Ignore:
Timestamp:
Apr 20, 2016 3:24:46 PM (8 years ago)
Author:
hellstea
Message:

Precomputation of ijfc for anterpolation added in pmc_interface_mod.f90

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/pmc_interface_mod.f90

    r1879 r1882  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! The factor ijfc for nfc used in anterpolation is redefined as 2-D array
     23! and precomputed in pmci_init_anterp_tophat.
    2324!
    2425! Former revisions:
     
    2728!
    2829! 1878 2016-04-19 12:30:36Z hellstea
    29 ! Synchronization rewritten, logc-array index order changed for cache optimization 
     30! Synchronization rewritten, logc-array index order changed for cache optimization
    3031!
    3132! 1850 2016-04-08 13:29:27Z maronga
     
    308309    INTEGER(iwp), SAVE, ALLOCATABLE, DIMENSION(:) ::  kfuo   !:
    309310
     311!
     312!-- Number of fine-grid nodes inside coarse-grid ij-faces
     313!-- to be precomputed for anterpolation.
     314    INTEGER(iwp), SAVE, ALLOCATABLE, DIMENSION(:,:) ::  ijfc_u        !:
     315    INTEGER(iwp), SAVE, ALLOCATABLE, DIMENSION(:,:) ::  ijfc_v        !:
     316    INTEGER(iwp), SAVE, ALLOCATABLE, DIMENSION(:,:) ::  ijfc_s        !:
     317   
    310318    INTEGER(iwp), DIMENSION(3)          ::  define_coarse_grid_int    !:
    311319    REAL(wp), DIMENSION(7)              ::  define_coarse_grid_real   !:
     
    20052013
    20062014       INTEGER(iwp) ::  i        !: Fine-grid index
     2015       INTEGER(iwp) ::  ifc_o    !:
     2016       INTEGER(iwp) ::  ifc_u    !:
    20072017       INTEGER(iwp) ::  ii       !: Coarse-grid index
    20082018       INTEGER(iwp) ::  istart   !:
     
    20632073       ALLOCATE( kfuo(0:kctu) )
    20642074
     2075       ALLOCATE( ijfc_u(jcs:jcn,icl:icr) )
     2076       ALLOCATE( ijfc_v(jcs:jcn,icl:icr) )
     2077       ALLOCATE( ijfc_s(jcs:jcn,icl:icr) )
     2078
    20652079!
    20662080!--    i-indices of u for each ii-index value
     
    21742188          kstart = kflo(kk)
    21752189       ENDDO
    2176      
     2190 
     2191!
     2192!--    Precomputation of number of fine-grid nodes inside coarse-grid ij-faces.
     2193!--    Note that ii, jj, and kk are coarse-grid indices.
     2194!--    This information is needed in anterpolation.
     2195       DO  ii = icl, icr
     2196          ifc_u = ifuu(ii) - iflu(ii) + 1
     2197          ifc_o = ifuo(ii) - iflo(ii) + 1
     2198          DO  jj = jcs, jcn
     2199             ijfc_u(jj,ii) = ifc_u * ( jfuo(jj) - jflo(jj) + 1 )
     2200             ijfc_v(jj,ii) = ifc_o * ( jfuv(jj) - jflv(jj) + 1 )
     2201             ijfc_s(jj,ii) = ifc_o * ( jfuo(jj) - jflo(jj) + 1 )             
     2202          ENDDO
     2203       ENDDO
     2204   
    21772205!
    21782206!--    Spatial under-relaxation coefficients
     
    30223050 SUBROUTINE pmci_datatrans( local_nesting_mode )
    30233051!
    3024 !-- Althoug nesting_mode is a variable of this model, pass it as an argument to
    3025 !-- allow for example to force one-way initialization phase
     3052!-- This subroutine controls the nesting according to the nestpar
     3053!-- parameter nesting_mode (two-way (default) or one-way) and the
     3054!-- order of anterpolations according to the nestpar parameter
     3055!-- nesting_datatransfer_mode (cascade, overlap or mixed (default)).
     3056!-- Although nesting_mode is a variable of this model, pass it as
     3057!-- an argument to allow for example to force one-way initialization
     3058!-- phase.
    30263059
    30273060    IMPLICIT NONE
     
    34023435!
    34033436!--   A wrapper routine for all anterpolation actions.
     3437!--   Note that TKE is not anterpolated.
    34043438      IMPLICIT NONE
    34053439
    34063440      CALL pmci_anterp_tophat( u,  uc,  kctu, iflu, ifuu, jflo, jfuo, kflo,    &
    3407                                kfuo, 'u' )
     3441                               kfuo, ijfc_u, 'u' )
    34083442      CALL pmci_anterp_tophat( v,  vc,  kctu, iflo, ifuo, jflv, jfuv, kflo,    &
    3409                                kfuo, 'v' )
     3443                               kfuo, ijfc_v, 'v' )
    34103444      CALL pmci_anterp_tophat( w,  wc,  kctw, iflo, ifuo, jflo, jfuo, kflw,    &
    3411                                kfuw, 'w' )
     3445                               kfuw, ijfc_s, 'w' )
    34123446      CALL pmci_anterp_tophat( pt, ptc, kctu, iflo, ifuo, jflo, jfuo, kflo,    &
    3413                                kfuo, 's' )
     3447                               kfuo, ijfc_s, 's' )
    34143448      IF ( humidity  .OR.  passive_scalar )  THEN
    34153449         CALL pmci_anterp_tophat( q, qc, kctu, iflo, ifuo, jflo, jfuo, kflo,   &
    3416                                   kfuo, 's' )
     3450                                  kfuo, ijfc_s, 's' )
    34173451      ENDIF
    34183452
     
    41184152
    41194153    SUBROUTINE pmci_anterp_tophat( f, fc, kct, ifl, ifu, jfl, jfu, kfl, kfu,   &
    4120                                    var )
     4154                                   ijfc, var )
    41214155!
    41224156!--    Anterpolation of internal-node values to be used as the server-domain
     
    41334167       INTEGER(iwp) ::  iclp      !:
    41344168       INTEGER(iwp) ::  icrm      !:
    4135        INTEGER(iwp) ::  ifc       !:
    4136        INTEGER(iwp) ::  ijfc      !:
    41374169       INTEGER(iwp) ::  j         !: Fine-grid index
    41384170       INTEGER(iwp) ::  jj        !: Coarse-grid index
     
    41534185       INTEGER(iwp), DIMENSION(0:kct), INTENT(IN)   ::  kfu   !:
    41544186
     4187       INTEGER(iwp), DIMENSION(jcs:jcn,icl:icr), INTENT(IN) ::  ijfc !:
    41554188
    41564189       REAL(wp) ::  cellsum   !:
     
    41974230
    41984231!
    4199 !--    Note that l,m, and n are coarse-grid indices and i,j, and k are fine-grid
    4200 !--    indices.
     4232!--    Note that ii, jj, and kk are coarse-grid indices and i,j, and k
     4233!--    are fine-grid indices.
    42014234       DO  ii = iclp, icrm
    4202           ifc = ifu(ii) - ifl(ii) + 1
    42034235          DO  jj = jcsp, jcnm
    4204              ijfc = ifc * ( jfu(jj) - jfl(jj) + 1 )
    42054236!
    42064237!--          For simplicity anterpolate within buildings too
    42074238             DO  kk = kcb, kct
    4208                 nfc =  ijfc * ( kfu(kk) - kfl(kk) + 1 )
     4239!
     4240!--             ijfc is precomputed in pmci_init_anterp_tophat
     4241                nfc =  ijfc(jj,ii) * ( kfu(kk) - kfl(kk) + 1 )
    42094242                cellsum = 0.0_wp
    42104243                DO  i = ifl(ii), ifu(ii)
     
    42254258                   ENDIF
    42264259                ENDIF
    4227 !
    4228 !--             TO DO: introduce 3-d coarse grid array for precomputed
    4229 !--             1/REAL(nfc) values
     4260
    42304261                fc(kk,jj,ii) = ( 1.0_wp - fra ) * fc(kk,jj,ii) +               &
    42314262                               fra * cellsum / REAL( nfc, KIND = wp )
Note: See TracChangeset for help on using the changeset viewer.