Changeset 12906
- Timestamp:
- 2020-05-11T19:19:46+02:00 (3 years ago)
- Location:
- NEMO/branches/UKMO/dev_r12866_HPC-02_Daley_Tiling_trial_extra_halo
- Files:
-
- 8 edited
Legend:
- Unmodified
- Added
- Removed
-
NEMO/branches/UKMO/dev_r12866_HPC-02_Daley_Tiling_trial_extra_halo/cfgs/SHARED/namelist_ref
r12866 r12906 94 94 ln_use_jattr = .false. ! use (T) the file attribute: open_ocean_jstart, if present 95 95 ! ! 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 96 103 / 97 104 !----------------------------------------------------------------------- -
NEMO/branches/UKMO/dev_r12866_HPC-02_Daley_Tiling_trial_extra_halo/src/OCE/DOM/dom_oce.F90
r12810 r12906 72 72 ! ! = 7 bi-cyclic East-West AND North-South 73 73 LOGICAL, PUBLIC :: l_Iperio, l_Jperio ! should we explicitely take care I/J periodicity 74 75 ! Tiling namelist 76 LOGICAL, PUBLIC :: ln_tile 77 INTEGER :: nn_ltile_i, nn_ltile_j 74 78 75 79 ! ! domain MPP decomposition parameters -
NEMO/branches/UKMO/dev_r12866_HPC-02_Daley_Tiling_trial_extra_halo/src/OCE/DOM/domain.F90
r12866 r12906 122 122 CALL dom_glo ! global domain versus local domain 123 123 CALL dom_nam ! read namelist ( namrun, namdom ) 124 CALL dom_tile ! Tile domains 125 124 126 ! 125 127 IF( lwxios ) THEN … … 270 272 271 273 274 SUBROUTINE dom_tile 275 !!---------------------------------------------------------------------- 276 !! *** ROUTINE dom_tile *** 277 !! 278 !! ** Purpose : Set tile domain variables 279 !! 280 !! ** Action : - ntsi, ntsj : start of internal part of domain 281 !! - ntei, ntej : end of internal part of domain 282 !! - nijtile : total number of tiles 283 !!---------------------------------------------------------------------- 284 INTEGER :: jt ! dummy loop argument 285 INTEGER :: iitile, ijtile ! Local integers 286 !!---------------------------------------------------------------------- 287 ntile = 0 ! Initialise to full domain 288 289 IF( ln_tile ) THEN ! Number of tiles 290 iitile = Ni_0 / nn_ltile_i 291 ijtile = Nj_0 / nn_ltile_j 292 IF( MOD( Ni_0, nn_ltile_i ) /= 0 ) iitile = iitile + 1 293 IF( MOD( Nj_0, nn_ltile_j ) /= 0 ) ijtile = ijtile + 1 294 295 nijtile = iitile * ijtile 296 ALLOCATE( ntsi(0:nijtile), ntsj(0:nijtile), ntei(0:nijtile), ntej(0:nijtile) ) 297 ELSE 298 nijtile = 1 299 ALLOCATE( ntsi(0:0), ntsj(0:0), ntei(0:0), ntej(0:0) ) 300 ENDIF 301 302 ntsi(0) = Nis0 ! Full domain 303 ntsj(0) = Njs0 304 ntei(0) = Nie0 305 ntej(0) = Nje0 306 307 IF( ln_tile ) THEN ! Tile domains 308 DO jt = 1, nijtile 309 ntsi(jt) = Nis0 + nn_ltile_i * MOD(jt - 1, iitile) 310 ntsj(jt) = Njs0 + nn_ltile_j * ((jt - 1) / iitile) 311 ntei(jt) = MIN(ntsi(jt) + nn_ltile_i - 1, Nie0) 312 ntej(jt) = MIN(ntsj(jt) + nn_ltile_j - 1, Nje0) 313 ENDDO 314 ENDIF 315 316 IF(lwp) THEN ! control print 317 WRITE(numout,*) 318 WRITE(numout,*) 'dom_tile : Domain tiling decomposition' 319 WRITE(numout,*) '~~~~~~~~' 320 IF( ln_tile ) THEN 321 WRITE(numout,*) iitile, 'tiles in i' 322 WRITE(numout,*) ' Starting indices' 323 WRITE(numout,*) ' ', (ntsi(jt), jt=1, iitile) 324 WRITE(numout,*) ' Ending indices' 325 WRITE(numout,*) ' ', (ntei(jt), jt=1, iitile) 326 WRITE(numout,*) ijtile, 'tiles in j' 327 WRITE(numout,*) ' Starting indices' 328 WRITE(numout,*) ' ', (ntsj(jt), jt=1, nijtile, iitile) 329 WRITE(numout,*) ' Ending indices' 330 WRITE(numout,*) ' ', (ntej(jt), jt=1, nijtile, iitile) 331 ELSE 332 WRITE(numout,*) 'No domain tiling' 333 WRITE(numout,*) ' i indices =', ntsi(0), ':', ntei(0) 334 WRITE(numout,*) ' j indices =', ntsj(0), ':', ntej(0) 335 ENDIF 336 ENDIF 337 END SUBROUTINE dom_tile 338 339 272 340 SUBROUTINE dom_nam 273 341 !!---------------------------------------------------------------------- … … 278 346 !! ** input : - namrun namelist 279 347 !! - namdom namelist 348 !! - namtile namelist 280 349 !! - namnc4 namelist ! "key_netcdf4" only 281 350 !!---------------------------------------------------------------------- … … 290 359 & ln_cfmeta, ln_xios_read, nn_wxios 291 360 NAMELIST/namdom/ ln_linssh, rn_Dt, rn_atfp, ln_crs, ln_meshmask 361 NAMELIST/namtile/ ln_tile, nn_ltile_i, nn_ltile_j 292 362 #if defined key_netcdf4 293 363 NAMELIST/namnc4/ nn_nchunks_i, nn_nchunks_j, nn_nchunks_k, ln_nc4zip … … 417 487 r1_Dt = 1._wp / rDt 418 488 489 READ ( numnam_ref, namtile, IOSTAT = ios, ERR = 905 ) 490 905 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtile in reference namelist' ) 491 READ ( numnam_cfg, namtile, IOSTAT = ios, ERR = 906 ) 492 906 IF( ios > 0 ) CALL ctl_nam ( ios , 'namtile in configuration namelist' ) 493 IF(lwm) WRITE( numond, namtile ) 494 495 IF(lwp) THEN 496 WRITE(numout,*) 497 WRITE(numout,*) ' Namelist : namtile --- Domain tiling decomposition' 498 WRITE(numout,*) ' Tiling (T) or not (F) ln_tile = ', ln_tile 499 WRITE(numout,*) ' Length of tile in i nn_ltile_i = ', nn_ltile_i 500 WRITE(numout,*) ' Length of tile in j nn_ltile_j = ', nn_ltile_j 501 WRITE(numout,*) 502 IF( ln_tile ) THEN 503 WRITE(numout,*) ' The domain will be decomposed into tiles of size', nn_ltile_i, 'x', nn_ltile_j 504 ELSE 505 WRITE(numout,*) ' Domain tiling will NOT be used' 506 ENDIF 507 ENDIF 508 419 509 IF( TRIM(Agrif_CFixed()) == '0' ) THEN 420 510 lrxios = ln_xios_read.AND.ln_rstart -
NEMO/branches/UKMO/dev_r12866_HPC-02_Daley_Tiling_trial_extra_halo/src/OCE/TRA/traldf.F90
r12377 r12906 58 58 !!---------------------------------------------------------------------- 59 59 ! 60 IF( ln_timing ) CALL timing_start('tra_ldf') 60 IF( ntile == 1 ) THEN ! Do only on the first tile 61 ! TODO: TO BE TILED 62 IF( ln_timing ) CALL timing_start('tra_ldf') 63 ENDIF 61 64 ! 62 IF( l_trdtra ) THEN !* Save ta and sa trends 63 ALLOCATE( ztrdt(jpi,jpj,jpk) , ztrds(jpi,jpj,jpk) ) 64 ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) 65 ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs) 65 IF( ntile == nijtile ) THEN ! Do only after all tiles finish 66 IF( l_trdtra ) THEN !* Save ta and sa trends 67 ! TODO: TO BE TILED 68 ALLOCATE( ztrdt(jpi,jpj,jpk) , ztrds(jpi,jpj,jpk) ) 69 ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) 70 ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs) 71 ENDIF 66 72 ENDIF 67 73 ! … … 77 83 END SELECT 78 84 ! 79 IF( l_trdtra ) THEN !* save the horizontal diffusive trends for further diagnostics 80 ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) - ztrdt(:,:,:) 81 ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs) - ztrds(:,:,:) 82 CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_ldf, ztrdt ) 83 CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_ldf, ztrds ) 84 DEALLOCATE( ztrdt, ztrds ) 85 IF( ntile == nijtile ) THEN ! Do only after all tiles finish 86 IF( l_trdtra ) THEN !* save the horizontal diffusive trends for further diagnostics 87 ! TODO: TO BE TILED 88 ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) - ztrdt(:,:,:) 89 ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs) - ztrds(:,:,:) 90 ! TODO: TO BE TILED 91 CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_ldf, ztrdt ) 92 CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_ldf, ztrds ) 93 DEALLOCATE( ztrdt, ztrds ) 94 ENDIF 95 96 ! !* print mean trends (used for debugging) 97 ! TODO: TO BE TILED 98 IF(sn_cfctl%l_prtctl) CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' ldf - Ta: ', mask1=tmask, & 99 & tab3d_2=pts(:,:,:,jp_sal,Krhs), clinfo2= ' Sa: ', mask2=tmask, clinfo3='tra' ) 100 ! 101 ! TODO: TO BE TILED 102 IF( ln_timing ) CALL timing_stop('tra_ldf') 85 103 ENDIF 86 ! !* print mean trends (used for debugging)87 IF(sn_cfctl%l_prtctl) CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' ldf - Ta: ', mask1=tmask, &88 & tab3d_2=pts(:,:,:,jp_sal,Krhs), clinfo2= ' Sa: ', mask2=tmask, clinfo3='tra' )89 !90 IF( ln_timing ) CALL timing_stop('tra_ldf')91 104 ! 92 105 END SUBROUTINE tra_ldf -
NEMO/branches/UKMO/dev_r12866_HPC-02_Daley_Tiling_trial_extra_halo/src/OCE/TRA/traldf_iso.F90
r12489 r12906 36 36 PUBLIC tra_ldf_iso ! routine called by step.F90 37 37 38 LOGICAL :: l_ptr ! flag to compute poleward transport39 LOGICAL :: l_hst ! flag to compute heat transport40 41 38 !! * Substitutions 42 39 # include "do_loop_substitute.h90" … … 104 101 REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(inout) :: pt_rhs ! tracer trend 105 102 ! 103 LOGICAL :: l_ptr ! flag to compute poleward transport 104 LOGICAL :: l_hst ! flag to compute heat transport 106 105 INTEGER :: ji, jj, jk, jn ! dummy loop indices 107 106 INTEGER :: ikt … … 110 109 REAL(wp) :: zmskv, zahv_w, zabe2, zcof2, zcoef4 ! - - 111 110 REAL(wp) :: zcoef0, ze3w_2, zsign ! - - 112 REAL(wp), DIMENSION( jpi,jpj) :: zdkt, zdk1t, z2d113 REAL(wp), DIMENSION( jpi,jpj,jpk) :: zdit, zdjt, zftu, zftv, ztfw111 REAL(wp), DIMENSION(A2D) :: zdkt, zdk1t, z2d 112 REAL(wp), DIMENSION(A2D,jpk) :: zdit, zdjt, zftu, zftv, ztfw 114 113 !!---------------------------------------------------------------------- 115 114 ! 116 115 IF( kpass == 1 .AND. kt == kit000 ) THEN 117 IF(lwp) WRITE(numout,*) 118 IF(lwp) WRITE(numout,*) 'tra_ldf_iso : rotated laplacian diffusion operator on ', cdtype 119 IF(lwp) WRITE(numout,*) '~~~~~~~~~~~' 120 ! 121 akz (:,:,:) = 0._wp 122 ah_wslp2(:,:,:) = 0._wp 116 IF( ntile == 1 ) THEN ! Do only on the first tile 117 ! TODO: TO BE TILED 118 IF(lwp) WRITE(numout,*) 119 IF(lwp) WRITE(numout,*) 'tra_ldf_iso : rotated laplacian diffusion operator on ', cdtype 120 IF(lwp) WRITE(numout,*) '~~~~~~~~~~~' 121 ENDIF 122 ! 123 DO_3D_11_11( 1, jpk ) 124 akz (ji,jj,jk) = 0._wp 125 ah_wslp2(ji,jj,jk) = 0._wp 126 END_3D 123 127 ENDIF 124 128 ! … … 179 183 ! 180 184 ELSE ! 33 flux set to zero with akz=ah_wslp2 ==>> computed in full implicit 181 akz(:,:,:) = ah_wslp2(:,:,:) 185 DO_3D_11_11( 1, jpk ) 186 akz(ji,jj,jk) = ah_wslp2(ji,jj,jk) 187 END_3D 182 188 ENDIF 183 189 ENDIF … … 219 225 DO jk = 1, jpkm1 ! Horizontal slab 220 226 ! 221 ! !== Vertical tracer gradient 222 zdk1t(:,:) = ( pt(:,:,jk,jn) - pt(:,:,jk+1,jn) ) * wmask(:,:,jk+1) ! level jk+1 223 ! 224 IF( jk == 1 ) THEN ; zdkt(:,:) = zdk1t(:,:) ! surface: zdkt(jk=1)=zdkt(jk=2) 225 ELSE ; zdkt(:,:) = ( pt(:,:,jk-1,jn) - pt(:,:,jk,jn) ) * wmask(:,:,jk) 226 ENDIF 227 DO_2D_11_11 228 ! !== Vertical tracer gradient 229 zdk1t(ji,jj) = ( pt(ji,jj,jk,jn) - pt(ji,jj,jk+1,jn) ) * wmask(ji,jj,jk+1) ! level jk+1 230 ! 231 IF( jk == 1 ) THEN ; zdkt(ji,jj) = zdk1t(ji,jj) ! surface: zdkt(jk=1)=zdkt(jk=2) 232 ELSE ; zdkt(ji,jj) = ( pt(ji,jj,jk-1,jn) - pt(ji,jj,jk,jn) ) * wmask(ji,jj,jk) 233 ENDIF 234 END_2D 235 ! 227 236 DO_2D_10_10 228 237 zabe1 = pahu(ji,jj,jk) * e2_e1u(ji,jj) * e3u(ji,jj,jk,Kmm) … … 312 321 END_3D 313 322 ! 314 IF( ( kpass == 1 .AND. ln_traldf_lap ) .OR. & !== first pass only ( laplacian) ==! 315 ( kpass == 2 .AND. ln_traldf_blp ) ) THEN !== 2nd pass (bilaplacian) ==! 316 ! 317 ! ! "Poleward" diffusive heat or salt transports (T-S case only) 318 ! note sign is reversed to give down-gradient diffusive transports ) 319 IF( l_ptr ) CALL dia_ptr_hst( jn, 'ldf', -zftv(:,:,:) ) 320 ! ! Diffusive heat transports 321 IF( l_hst ) CALL dia_ar5_hst( jn, 'ldf', -zftu(:,:,:), -zftv(:,:,:) ) 322 ! 323 ENDIF !== end pass selection ==! 323 IF( ntile == nijtile ) THEN ! Do only after all tiles finish 324 IF( ( kpass == 1 .AND. ln_traldf_lap ) .OR. & !== first pass only ( laplacian) ==! 325 ( kpass == 2 .AND. ln_traldf_blp ) ) THEN !== 2nd pass (bilaplacian) ==! 326 ! 327 ! ! "Poleward" diffusive heat or salt transports (T-S case only) 328 ! note sign is reversed to give down-gradient diffusive transports ) 329 ! TODO: TO BE TILED 330 IF( l_ptr ) CALL dia_ptr_hst( jn, 'ldf', -zftv(:,:,:) ) 331 ! ! Diffusive heat transports 332 ! TODO: TO BE TILED 333 IF( l_hst ) CALL dia_ar5_hst( jn, 'ldf', -zftu(:,:,:), -zftv(:,:,:) ) 334 ! 335 ENDIF !== end pass selection ==! 336 ENDIF 324 337 ! 325 338 ! ! =============== -
NEMO/branches/UKMO/dev_r12866_HPC-02_Daley_Tiling_trial_extra_halo/src/OCE/do_loop_substitute.h90
r12807 r12906 102 102 103 103 ! 2D loops with 1 104 105 #define DO_2D_00_00 DO jj = Njs0, Nje0 ; DO ji = Nis0, Nie0 106 #define DO_2D_00_01 DO jj = Njs0, Nje0 ; DO ji = Nis0, Nie1 107 #define DO_2D_00_10 DO jj = Njs0, Nje0 ; DO ji = Nis1, Nie0 108 #define DO_2D_00_11 DO jj = Njs0, Nje0 ; DO ji = Nis1, Nie1 104 #define Ntis0 ntsi(ntile) 105 #define Ntjs0 ntsj(ntile) 106 #define Ntis1 Ntis0 - 1 107 #define Ntjs1 Ntjs0 - 1 108 #define Ntis2 Ntis0 - nn_hls 109 #define Ntjs2 Ntjs0 - nn_hls 110 #define Ntie0 ntei(ntile) 111 #define Ntje0 ntej(ntile) 112 #define Ntie1 Ntie0 + 1 113 #define Ntje1 Ntje0 + 1 114 #define Ntie2 Ntie0 + nn_hls 115 #define Ntje2 Ntje0 + nn_hls 116 #define A2D Ntis2:Ntie2,Ntjs2:Ntje2 117 118 #define DO_2D_00_00 DO jj = Ntjs0, Ntje0 ; DO ji = Ntis0, Ntie0 119 #define DO_2D_00_01 DO jj = Ntjs0, Ntje0 ; DO ji = Ntis0, Ntie1 120 #define DO_2D_00_10 DO jj = Ntjs0, Ntje0 ; DO ji = Ntis1, Ntie0 121 #define DO_2D_00_11 DO jj = Ntjs0, Ntje0 ; DO ji = Ntis1, Ntie1 109 122 110 #define DO_2D_01_00 DO jj = N js0, Nje1 ; DO ji = Nis0, Nie0111 #define DO_2D_01_01 DO jj = N js0, Nje1 ; DO ji = Nis0, Nie1112 #define DO_2D_01_10 DO jj = N js0, Nje1 ; DO ji = Nis1, Nie0113 #define DO_2D_01_11 DO jj = N js0, Nje1 ; DO ji = Nis1, Nie1123 #define DO_2D_01_00 DO jj = Ntjs0, Ntje1 ; DO ji = Ntis0, Ntie0 124 #define DO_2D_01_01 DO jj = Ntjs0, Ntje1 ; DO ji = Ntis0, Ntie1 125 #define DO_2D_01_10 DO jj = Ntjs0, Ntje1 ; DO ji = Ntis1, Ntie0 126 #define DO_2D_01_11 DO jj = Ntjs0, Ntje1 ; DO ji = Ntis1, Ntie1 114 127 115 #define DO_2D_10_00 DO jj = N js1, Nje0 ; DO ji = Nis0, Nie0116 #define DO_2D_10_01 DO jj = N js1, Nje0 ; DO ji = Nis0, Nie1 ! not used ?117 #define DO_2D_10_10 DO jj = N js1, Nje0 ; DO ji = Nis1, Nie0118 #define DO_2D_10_11 DO jj = N js1, Nje0 ; DO ji = Nis1, Nie1128 #define DO_2D_10_00 DO jj = Ntjs1, Ntje0 ; DO ji = Ntis0, Ntie0 129 #define DO_2D_10_01 DO jj = Ntjs1, Ntje0 ; DO ji = Ntis0, Ntie1 ! not used ? 130 #define DO_2D_10_10 DO jj = Ntjs1, Ntje0 ; DO ji = Ntis1, Ntie0 131 #define DO_2D_10_11 DO jj = Ntjs1, Ntje0 ; DO ji = Ntis1, Ntie1 119 132 120 #define DO_2D_11_00 DO jj = N js1, Nje1 ; DO ji = Nis0, Nie0121 #define DO_2D_11_01 DO jj = N js1, Nje1 ; DO ji = Nis0, Nie1122 #define DO_2D_11_10 DO jj = N js1, Nje1 ; DO ji = Nis1, Nie0123 #define DO_2D_11_11 DO jj = N js1, Nje1 ; DO ji = Nis1, Nie1133 #define DO_2D_11_00 DO jj = Ntjs1, Ntje1 ; DO ji = Ntis0, Ntie0 134 #define DO_2D_11_01 DO jj = Ntjs1, Ntje1 ; DO ji = Ntis0, Ntie1 135 #define DO_2D_11_10 DO jj = Ntjs1, Ntje1 ; DO ji = Ntis1, Ntie0 136 #define DO_2D_11_11 DO jj = Ntjs1, Ntje1 ; DO ji = Ntis1, Ntie1 124 137 125 138 ! 2D loops with 1 following a 2/3D loop with 2 -
NEMO/branches/UKMO/dev_r12866_HPC-02_Daley_Tiling_trial_extra_halo/src/OCE/par_oce.F90
r12807 r12906 62 62 INTEGER, PUBLIC :: jpjmax! = ( jpjglo-2*nn_hls + (jpnj-1) ) / jpnj + 2*nn_hls !: maximum jpj 63 63 64 ! Domain tiling 65 INTEGER, PUBLIC :: nijtile !: number of tiles in total 66 INTEGER, PUBLIC :: ntile !: current tile number 67 INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: ntsi !: start of internal part of tile domain 68 INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: ntsj ! 69 INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: ntei !: end of internal part of tile domain 70 INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: ntej ! 71 64 72 !!--------------------------------------------------------------------- 65 73 !! Active tracer parameters -
NEMO/branches/UKMO/dev_r12866_HPC-02_Daley_Tiling_trial_extra_halo/src/OCE/step.F90
r12489 r12906 81 81 !! -8- Outputs and diagnostics 82 82 !!---------------------------------------------------------------------- 83 INTEGER :: ji, jj, jk ! dummy loop indice83 INTEGER :: ji, jj, jk, jtile ! dummy loop indice 84 84 INTEGER :: indic ! error indicator if < 0 85 85 !!gm kcall can be removed, I guess … … 263 263 IF( lrst_oce .AND. ln_zdfosm ) & 264 264 & CALL osm_rst ( kstp, Nnn, 'WRITE' ) ! write OSMOSIS outputs + ww (so must do here) to restarts 265 266 ! Loop over tile domains 267 DO jtile = 1, nijtile 268 IF( ln_tile ) ntile = jtile 265 269 CALL tra_ldf ( kstp, Nbb, Nnn, ts, Nrhs ) ! lateral mixing 266 270 END DO 271 IF( ln_tile ) ntile = 0 ! Revert to tile over full domain 267 272 CALL tra_zdf ( kstp, Nbb, Nnn, Nrhs, ts, Naa ) ! vertical mixing and after tracer fields 268 273 IF( ln_zdfnpc ) CALL tra_npc ( kstp, Nnn, Nrhs, ts, Naa ) ! update after fields by non-penetrative convection
Note: See TracChangeset
for help on using the changeset viewer.