New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 13514 – NEMO

Changeset 13514


Ignore:
Timestamp:
2020-09-24T20:29:14+02:00 (4 years ago)
Author:
hadcv
Message:

Tiling variables, functions and namelist

Location:
NEMO/branches/2020/dev_r13383_HPC-02_Daley_Tiling
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_r13383_HPC-02_Daley_Tiling/cfgs/SHARED/namelist_ref

    r13286 r13514  
    9494   ln_use_jattr = .false.    !  use (T) the file attribute: open_ocean_jstart, if present 
    9595   !                         !  in netcdf input files, as the start j-row for reading 
     96/ 
     97!----------------------------------------------------------------------- 
     98&namtile        !   parameters of the tiling 
     99!----------------------------------------------------------------------- 
     100   ln_tile = .false.     !  Use tiling (T) or not (F) 
     101   nn_ltile_i = 10       !  Length of tiles in i 
     102   nn_ltile_j = 10       !  Length of tiles in j 
    96103/ 
    97104!----------------------------------------------------------------------- 
  • NEMO/branches/2020/dev_r13383_HPC-02_Daley_Tiling/src/OCE/DOM/dom_oce.F90

    r13286 r13514  
    7373   !                                !  = 7 bi-cyclic East-West AND North-South 
    7474   LOGICAL, PUBLIC ::   l_Iperio, l_Jperio   !   should we explicitely take care I/J periodicity  
     75 
     76   ! Tiling namelist 
     77   LOGICAL, PUBLIC ::   ln_tile 
     78   INTEGER         ::   nn_ltile_i, nn_ltile_j 
     79 
     80   ! Domain tiling (all tiles) 
     81   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   ntsi_a       !: start of internal part of tile domain 
     82   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   ntsj_a       ! 
     83   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   ntei_a       !: end of internal part of tile domain 
     84   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   ntej_a       ! 
    7585 
    7686   !                             !: domain MPP decomposition parameters 
     
    291301      ALLOCATE( e3t(jpi,jpj,jpk,jpt) , e3u (jpi,jpj,jpk,jpt) , e3v (jpi,jpj,jpk,jpt) , e3f(jpi,jpj,jpk) ,      & 
    292302         &      e3w(jpi,jpj,jpk,jpt) , e3uw(jpi,jpj,jpk,jpt) , e3vw(jpi,jpj,jpk,jpt)                    ,  STAT=ierr(ii) ) 
    293 #endif   
     303#endif 
    294304         ! 
    295305      ii = ii+1 
    296306      ALLOCATE( r3t  (jpi,jpj,jpt)   , r3u  (jpi,jpj,jpt)    , r3v  (jpi,jpj,jpt)    , r3f  (jpi,jpj) ,  & 
    297          &      r3t_f(jpi,jpj)       , r3u_f(jpi,jpj)        , r3v_f(jpi,jpj)                         ,  STAT=ierr(ii) )        
     307         &      r3t_f(jpi,jpj)       , r3u_f(jpi,jpj)        , r3v_f(jpi,jpj)                         ,  STAT=ierr(ii) ) 
    298308         ! 
    299309      ii = ii+1 
     
    312322         ! 
    313323      ii = ii+1 
    314       ALLOCATE( risfdep(jpi,jpj) , bathy(jpi,jpj) , STAT=ierr(ii)  )  
     324      ALLOCATE( risfdep(jpi,jpj) , bathy(jpi,jpj) , STAT=ierr(ii)  ) 
    315325         ! 
    316326      ii = ii+1 
     
    318328         ! 
    319329      ii = ii+1 
    320       ALLOCATE( tmask_i(jpi,jpj) , tmask_h(jpi,jpj) ,                        &  
     330      ALLOCATE( tmask_i(jpi,jpj) , tmask_h(jpi,jpj) ,                        & 
    321331         &      ssmask (jpi,jpj) , ssumask(jpi,jpj) , ssvmask(jpi,jpj) , ssfmask(jpi,jpj) ,     & 
    322332         &      mbkt   (jpi,jpj) , mbku   (jpi,jpj) , mbkv   (jpi,jpj) ,                    STAT=ierr(ii) ) 
     
    326336         ! 
    327337      ii = ii+1 
    328       ALLOCATE( tmask(jpi,jpj,jpk) , umask(jpi,jpj,jpk) ,     &  
     338      ALLOCATE( tmask(jpi,jpj,jpk) , umask(jpi,jpj,jpk) ,     & 
    329339         &      vmask(jpi,jpj,jpk) , fmask(jpi,jpj,jpk) , STAT=ierr(ii) ) 
    330340         ! 
  • NEMO/branches/2020/dev_r13383_HPC-02_Daley_Tiling/src/OCE/DOM/domain.F90

    r13286 r13514  
    5555   PUBLIC   dom_init     ! called by nemogcm.F90 
    5656   PUBLIC   domain_cfg   ! called by nemogcm.F90 
     57   PUBLIC   dom_tile     ! called by step.F90 
    5758 
    5859   !!------------------------------------------------------------------------- 
     
    125126      !           !==  Reference coordinate system  ==! 
    126127      ! 
    127       CALL dom_glo                     ! global domain versus local domain 
    128       CALL dom_nam                     ! read namelist ( namrun, namdom ) 
     128      CALL dom_glo                            ! global domain versus local domain 
     129      CALL dom_nam                            ! read namelist ( namrun, namdom ) 
     130      CALL dom_tile( ntsi, ntsj, ntei, ntej ) ! Tile domain 
     131 
    129132      ! 
    130133      IF( lwxios ) THEN 
     
    287290 
    288291 
     292   SUBROUTINE dom_tile( ktsi, ktsj, ktei, ktej, ktile ) 
     293      !!---------------------------------------------------------------------- 
     294      !!                     ***  ROUTINE dom_tile  *** 
     295      !! 
     296      !! ** Purpose :   Set tile domain variables 
     297      !! 
     298      !! ** Action  : - ktsi, ktsj     : start of internal part of domain 
     299      !!              - ktei, ktej     : end of internal part of domain 
     300      !!              - ntile          : current tile number 
     301      !!              - nijtile        : total number of tiles 
     302      !!---------------------------------------------------------------------- 
     303      INTEGER, INTENT(out) :: ktsi, ktsj, ktei, ktej      ! Tile domain indices 
     304      INTEGER, INTENT(in), OPTIONAL :: ktile              ! Tile number 
     305      INTEGER ::   jt                                     ! dummy loop argument 
     306      INTEGER ::   iitile, ijtile                         ! Local integers 
     307      !!---------------------------------------------------------------------- 
     308      IF( PRESENT(ktile) .AND. ln_tile ) THEN 
     309         ntile = ktile                 ! Set domain indices for tile 
     310         ktsi = ntsi_a(ktile) 
     311         ktsj = ntsj_a(ktile) 
     312         ktei = ntei_a(ktile) 
     313         ktej = ntej_a(ktile) 
     314      ELSE 
     315         ntile = 0                     ! Initialise to full domain 
     316         nijtile = 1 
     317         ktsi = Nis0 
     318         ktsj = Njs0 
     319         ktei = Nie0 
     320         ktej = Nje0 
     321 
     322         IF( ln_tile ) THEN            ! Calculate tile domain indices 
     323            iitile = Ni_0 / nn_ltile_i       ! Number of tiles 
     324            ijtile = Nj_0 / nn_ltile_j 
     325            IF( MOD( Ni_0, nn_ltile_i ) /= 0 ) iitile = iitile + 1 
     326            IF( MOD( Nj_0, nn_ltile_j ) /= 0 ) ijtile = ijtile + 1 
     327 
     328            nijtile = iitile * ijtile 
     329            ALLOCATE( ntsi_a(0:nijtile), ntsj_a(0:nijtile), ntei_a(0:nijtile), ntej_a(0:nijtile) ) 
     330 
     331            ntsi_a(0) = ktsi                 ! Full domain 
     332            ntsj_a(0) = ktsj 
     333            ntei_a(0) = ktei 
     334            ntej_a(0) = ktej 
     335 
     336            DO jt = 1, nijtile               ! Tile domains 
     337               ntsi_a(jt) = Nis0 + nn_ltile_i * MOD(jt - 1, iitile) 
     338               ntsj_a(jt) = Njs0 + nn_ltile_j * ((jt - 1) / iitile) 
     339               ntei_a(jt) = MIN(ntsi_a(jt) + nn_ltile_i - 1, Nie0) 
     340               ntej_a(jt) = MIN(ntsj_a(jt) + nn_ltile_j - 1, Nje0) 
     341            ENDDO 
     342         ENDIF 
     343 
     344         IF(lwp) THEN                  ! control print 
     345            WRITE(numout,*) 
     346            WRITE(numout,*) 'dom_tile : Domain tiling decomposition' 
     347            WRITE(numout,*) '~~~~~~~~' 
     348            IF( ln_tile ) THEN 
     349               WRITE(numout,*) iitile, 'tiles in i' 
     350               WRITE(numout,*) '    Starting indices' 
     351               WRITE(numout,*) '        ', (ntsi_a(jt), jt=1, iitile) 
     352               WRITE(numout,*) '    Ending indices' 
     353               WRITE(numout,*) '        ', (ntei_a(jt), jt=1, iitile) 
     354               WRITE(numout,*) ijtile, 'tiles in j' 
     355               WRITE(numout,*) '    Starting indices' 
     356               WRITE(numout,*) '        ', (ntsj_a(jt), jt=1, nijtile, iitile) 
     357               WRITE(numout,*) '    Ending indices' 
     358               WRITE(numout,*) '        ', (ntej_a(jt), jt=1, nijtile, iitile) 
     359            ELSE 
     360               WRITE(numout,*) 'No domain tiling' 
     361               WRITE(numout,*) '    i indices =', ktsi, ':', ktei 
     362               WRITE(numout,*) '    j indices =', ktsj, ':', ktej 
     363            ENDIF 
     364         ENDIF 
     365      ENDIF 
     366   END SUBROUTINE dom_tile 
     367 
     368 
    289369   SUBROUTINE dom_nam 
    290370      !!---------------------------------------------------------------------- 
     
    295375      !! ** input   : - namrun namelist 
    296376      !!              - namdom namelist 
     377      !!              - namtile namelist 
    297378      !!              - namnc4 namelist   ! "key_netcdf4" only 
    298379      !!---------------------------------------------------------------------- 
     
    307388         &             ln_cfmeta, ln_xios_read, nn_wxios 
    308389      NAMELIST/namdom/ ln_linssh, rn_Dt, rn_atfp, ln_crs, ln_meshmask 
     390      NAMELIST/namtile/ ln_tile, nn_ltile_i, nn_ltile_j 
    309391#if defined key_netcdf4 
    310392      NAMELIST/namnc4/ nn_nchunks_i, nn_nchunks_j, nn_nchunks_k, ln_nc4zip 
     
    443525      r1_Dt = 1._wp / rDt 
    444526 
     527      READ  ( numnam_ref, namtile, IOSTAT = ios, ERR = 905 ) 
     528905   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtile in reference namelist' ) 
     529      READ  ( numnam_cfg, namtile, IOSTAT = ios, ERR = 906 ) 
     530906   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtile in configuration namelist' ) 
     531      IF(lwm) WRITE( numond, namtile ) 
     532 
     533      IF(lwp) THEN 
     534         WRITE(numout,*) 
     535         WRITE(numout,*)    '   Namelist : namtile   ---   Domain tiling decomposition' 
     536         WRITE(numout,*)    '      Tiling (T) or not (F)                ln_tile    = ', ln_tile 
     537         WRITE(numout,*)    '      Length of tile in i                  nn_ltile_i = ', nn_ltile_i 
     538         WRITE(numout,*)    '      Length of tile in j                  nn_ltile_j = ', nn_ltile_j 
     539         WRITE(numout,*) 
     540         IF( ln_tile ) THEN 
     541            WRITE(numout,*) '      The domain will be decomposed into tiles of size', nn_ltile_i, 'x', nn_ltile_j 
     542         ELSE 
     543            WRITE(numout,*) '      Domain tiling will NOT be used' 
     544         ENDIF 
     545      ENDIF 
     546 
    445547      IF( TRIM(Agrif_CFixed()) == '0' ) THEN 
    446548         lrxios = ln_xios_read.AND.ln_rstart 
  • NEMO/branches/2020/dev_r13383_HPC-02_Daley_Tiling/src/OCE/DOM/domutl.F90

    r13286 r13514  
    2121   PRIVATE 
    2222 
     23   INTERFACE is_tile 
     24      MODULE PROCEDURE is_tile_2d, is_tile_3d, is_tile_4d 
     25   END INTERFACE is_tile 
     26 
    2327   PUBLIC dom_ngb    ! routine called in iom.F90 module 
    2428   PUBLIC dom_uniq   ! Called by dommsk and domwri 
     29   PUBLIC is_tile 
    2530 
    2631   !!---------------------------------------------------------------------- 
     
    115120      ! 
    116121   END SUBROUTINE dom_uniq 
    117     
     122 
     123 
     124   PURE FUNCTION is_tile_2d( pt ) 
     125      !! 
     126      REAL(wp), DIMENSION(:,:), INTENT(in) ::   pt 
     127      INTEGER :: is_tile_2d 
     128      !! 
     129      IF( ln_tile .AND. SIZE(pt, 1) < jpi ) THEN 
     130         is_tile_2d = 1 
     131      ELSE 
     132         is_tile_2d = 0 
     133      ENDIF 
     134   END FUNCTION is_tile_2d 
     135 
     136 
     137   PURE FUNCTION is_tile_3d( pt ) 
     138      !! 
     139      REAL(wp), DIMENSION(:,:,:), INTENT(in) ::   pt 
     140      INTEGER :: is_tile_3d 
     141      !! 
     142      IF( ln_tile .AND. SIZE(pt, 1) < jpi ) THEN 
     143         is_tile_3d = 1 
     144      ELSE 
     145         is_tile_3d = 0 
     146      ENDIF 
     147   END FUNCTION is_tile_3d 
     148 
     149 
     150   PURE FUNCTION is_tile_4d( pt ) 
     151      !! 
     152      REAL(wp), DIMENSION(:,:,:,:), INTENT(in) ::   pt 
     153      INTEGER :: is_tile_4d 
     154      !! 
     155      IF( ln_tile .AND. SIZE(pt, 1) < jpi ) THEN 
     156         is_tile_4d = 1 
     157      ELSE 
     158         is_tile_4d = 0 
     159      ENDIF 
     160   END FUNCTION is_tile_4d 
     161 
    118162   !!====================================================================== 
    119163END MODULE domutl 
  • NEMO/branches/2020/dev_r13383_HPC-02_Daley_Tiling/src/OCE/do_loop_substitute.h90

    r13296 r13514  
    5959#endif 
    6060 
    61 #define DO_2D(B, T, L, R) DO jj = Njs0-(B), Nje0+(T)   ;   DO ji = Nis0-(L), Nie0+(R) 
     61#define DO_2D(B, T, L, R) DO jj = ntsj-(B), ntej+(T)   ;   DO ji = ntsi-(L), ntei+(R) 
     62#define ST_1Di(H) ntsi-H:ntei+H 
     63#define ST_1Dj(H) ntsj-H:ntej+H 
     64#define ST_2D(H) ST_1Di(H),ST_1Dj(H) 
     65#define ST_1DTi(T) (ntsi-nn_hls-1)*T+1:(ntei+nn_hls-jpi)*T+jpi 
     66#define ST_1DTj(T) (ntsj-nn_hls-1)*T+1:(ntej+nn_hls-jpj)*T+jpj 
     67#define ST_2DT(T) ST_1DTi(T),ST_1DTj(T) 
    6268 
    6369#define DO_3D(B, T, L, R, ks, ke) DO jk = ks, ke   ;   DO_2D(B, T, L, R) 
  • NEMO/branches/2020/dev_r13383_HPC-02_Daley_Tiling/src/OCE/par_oce.F90

    r13286 r13514  
    6565   INTEGER, PUBLIC ::   jpjmax! = ( Nj0glo + jpnj-1 ) / jpnj + 2*nn_hls            !: maximum jpj 
    6666 
     67   ! Domain tiling 
     68   INTEGER, PUBLIC ::   nijtile    !: number of tiles in total 
     69   INTEGER, PUBLIC ::   ntile      !: current tile number 
     70   INTEGER, PUBLIC ::   ntsi       !: start of internal part of tile domain 
     71   INTEGER, PUBLIC ::   ntsj       ! 
     72   INTEGER, PUBLIC ::   ntei       !: end of internal part of tile domain 
     73   INTEGER, PUBLIC ::   ntej       ! 
     74 
    6775   !!--------------------------------------------------------------------- 
    6876   !! Active tracer parameters 
  • NEMO/branches/2020/dev_r13383_HPC-02_Daley_Tiling/src/OCE/step_oce.F90

    r12377 r13514  
    99   USE oce             ! ocean dynamics and tracers variables 
    1010   USE dom_oce         ! ocean space and time domain variables 
     11   USE domain, ONLY : dom_tile 
    1112   USE zdf_oce         ! ocean vertical physics variables 
    1213   USE zdfdrg  ,  ONLY : ln_drgimp   ! implicit top/bottom friction 
Note: See TracChangeset for help on using the changeset viewer.