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.
Diff from NEMO/branches/2021/dev_r14393_HPC-03_Mele_Comm_Cleanup/src/OCE/ZDF/zdfphy.F90@14757 to NEMO/branches/2021/dev_r14273_HPC-02_Daley_Tiling/src/OCE/ZDF/zdfphy.F90@14787 – NEMO

Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/dev_r14273_HPC-02_Daley_Tiling/src/OCE/ZDF/zdfphy.F90

    r14757 r14787  
    1212   !!---------------------------------------------------------------------- 
    1313   USE oce            ! ocean dynamics and tracers variables 
     14   ! TEMP: [tiling] This change not necessary after finalisation of zdf_osm (not yet tiled) 
     15   USE domtile 
    1416   USE zdf_oce        ! vertical physics: shared variables 
    1517   USE zdfdrg         ! vertical physics: top/bottom drag coef. 
     
    5658   LOGICAL, PUBLIC ::   l_zdfsh2   ! shear production term flag (=F for CST, =T otherwise (i.e. TKE, GLS, RIC)) 
    5759 
     60   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:,:) ::   avm_k_n !: "Now" avm_k used for calculation of zsh2 with tiling 
     61 
     62   !! * Substitutions 
     63#  include "do_loop_substitute.h90" 
    5864   !!---------------------------------------------------------------------- 
    5965   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     
    180186      IF( lk_top    .AND. ln_zdfnpc )   CALL ctl_stop( 'zdf_phy_init: npc scheme is not working with key_top' ) 
    181187      IF( lk_top    .AND. ln_zdfosm )   CALL ctl_warn( 'zdf_phy_init: osmosis gives no non-local fluxes for TOP tracers yet' ) 
     188      ! TEMP: [tiling] This change not necessary after finalisation of zdf_osm (not yet tiled) 
     189      IF( ln_tile   .AND. ln_zdfosm )   CALL ctl_warn( 'zdf_phy_init: osmosis does not yet work with tiling' ) 
    182190      IF( lk_top    .AND. ln_zdfmfc )   CALL ctl_stop( 'zdf_phy_init: Mass Flux scheme is not working with key_top' ) 
    183191      IF(lwp) THEN 
     
    210218      ENDIF 
    211219      !                                ! shear production term flag 
    212       IF( ln_zdfcst ) THEN   ;   l_zdfsh2 = .FALSE. 
    213       ELSE                   ;   l_zdfsh2 = .TRUE. 
    214       ENDIF 
     220      IF( ln_zdfcst .OR. ln_zdfosm ) THEN   ;   l_zdfsh2 = .FALSE. 
     221      ELSE                                  ;   l_zdfsh2 = .TRUE. 
     222      ENDIF 
     223      IF( ln_tile .AND. l_zdfsh2 ) ALLOCATE( avm_k_n(jpi,jpj,jpk) ) 
    215224      !                          !== Mass Flux Convectiive algorithm  ==! 
    216225      IF( ln_zdfmfc )   CALL zdf_mfc_init       ! Convection computed with eddy diffusivity mass flux 
     
    246255      ! 
    247256      INTEGER ::   ji, jj, jk   ! dummy loop indice 
    248       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zsh2   ! shear production 
     257      REAL(wp), DIMENSION(A2D(nn_hls),jpk) ::   zsh2   ! shear production 
     258      ! TEMP: [tiling] This change not necessary after finalisation of zdf_osm (not yet tiled) 
     259      LOGICAL :: lskip 
    249260      !! --------------------------------------------------------------------- 
    250261      ! 
    251262      IF( ln_timing )   CALL timing_start('zdf_phy') 
     263 
     264      ! TEMP: [tiling] These changes not necessary after finalisation of zdf_osm (not yet tiled) 
     265      lskip = .FALSE. 
     266 
     267      IF( ln_tile .AND. nzdf_phy == np_OSM )  THEN 
     268         IF( ntile == 1 ) THEN 
     269            CALL dom_tile_stop( ldhold=.TRUE. ) 
     270         ELSE 
     271            lskip = .TRUE. 
     272         ENDIF 
     273      ENDIF 
    252274      ! 
    253275      IF( l_zdfdrg ) THEN     !==  update top/bottom drag  ==!   (non-linear cases) 
     
    267289      IF ( ln_drgice_imp) THEN 
    268290         IF ( ln_isfcav ) THEN 
    269             rCdU_top(:,:) = rCdU_top(:,:) + ssmask(:,:) * tmask(:,:,1) * rCdU_ice(:,:) 
     291            DO_2D_OVR( 1, 1, 1, 1 ) 
     292               rCdU_top(ji,jj) = rCdU_top(ji,jj) + ssmask(ji,jj) * tmask(ji,jj,1) * rCdU_ice(ji,jj) 
     293            END_2D 
    270294         ELSE 
    271             rCdU_top(:,:) = rCdU_ice(:,:) 
     295            DO_2D_OVR( 1, 1, 1, 1 ) 
     296               rCdU_top(ji,jj) = rCdU_ice(ji,jj) 
     297            END_2D 
    272298         ENDIF 
    273299      ENDIF 
    274300#endif 
    275301      ! 
    276       !                       !==  Kz from chosen turbulent closure  ==!   (avm_k, avt_k) 
    277       ! 
    278       IF( l_zdfsh2 )   &         !* shear production at w-points (energy conserving form) 
    279          CALL zdf_sh2( Kbb, Kmm, avm_k,   &     ! <<== in 
    280             &                     zsh2    )     ! ==>> out : shear production 
    281       ! 
    282       SELECT CASE ( nzdf_phy )                  !* Vertical eddy viscosity and diffusivity coefficients at w-points 
    283       CASE( np_RIC )   ;   CALL zdf_ric( kt,      Kmm, zsh2, avm_k, avt_k )    ! Richardson number dependent Kz 
    284       CASE( np_TKE )   ;   CALL zdf_tke( kt, Kbb, Kmm, zsh2, avm_k, avt_k )    ! TKE closure scheme for Kz 
    285       CASE( np_GLS )   ;   CALL zdf_gls( kt, Kbb, Kmm, zsh2, avm_k, avt_k )    ! GLS closure scheme for Kz 
    286       CASE( np_OSM )   ;   CALL zdf_osm( kt, Kbb, Kmm, Krhs, avm_k, avt_k )    ! OSMOSIS closure scheme for Kz 
    287 !     CASE( np_CST )                                  ! Constant Kz (reset avt, avm to the background value) 
    288 !         ! avt_k and avm_k set one for all at initialisation phase 
     302      CALL zdf_mxl( kt, Kmm )                        !* mixed layer depth, and level 
     303 
     304      ! TEMP: [tiling] These changes not necessary after finalisation of zdf_osm (not yet tiled) 
     305      IF( .NOT. lskip ) THEN 
     306         !                       !==  Kz from chosen turbulent closure  ==!   (avm_k, avt_k) 
     307         ! 
     308         ! NOTE: [tiling] the closure schemes (zdf_tke etc) will update avm_k. With tiling, the calculation of zsh2 on adjacent tiles then uses both updated (next timestep) and non-updated (current timestep) values of avm_k. To preserve results, we save a read-only copy of the "now" avm_k to use in the calculation of zsh2. 
     309         IF( l_zdfsh2 ) THEN        !* shear production at w-points (energy conserving form) 
     310            IF( ln_tile ) THEN 
     311               IF( ntile == 1 ) avm_k_n(:,:,:) = avm_k(:,:,:)     ! Preserve "now" avm_k for calculation of zsh2 
     312               CALL zdf_sh2( Kbb, Kmm, avm_k_n, &     ! <<== in 
     313                  &                     zsh2    )     ! ==>> out : shear production 
     314            ELSE 
     315               CALL zdf_sh2( Kbb, Kmm, avm_k,   &     ! <<== in 
     316                  &                     zsh2    )     ! ==>> out : shear production 
     317            ENDIF 
     318         ENDIF 
     319         ! 
     320         SELECT CASE ( nzdf_phy )                  !* Vertical eddy viscosity and diffusivity coefficients at w-points 
     321         CASE( np_RIC )   ;   CALL zdf_ric( kt,      Kmm, zsh2, avm_k, avt_k )    ! Richardson number dependent Kz 
     322         CASE( np_TKE )   ;   CALL zdf_tke( kt, Kbb, Kmm, zsh2, avm_k, avt_k )    ! TKE closure scheme for Kz 
     323         CASE( np_GLS )   ;   CALL zdf_gls( kt, Kbb, Kmm, zsh2, avm_k, avt_k )    ! GLS closure scheme for Kz 
     324         CASE( np_OSM )   ;   CALL zdf_osm( kt, Kbb, Kmm, Krhs, avm_k, avt_k )    ! OSMOSIS closure scheme for Kz 
     325   !     CASE( np_CST )                                  ! Constant Kz (reset avt, avm to the background value) 
     326   !         ! avt_k and avm_k set one for all at initialisation phase 
    289327!!gm         avt(2:jpim1,2:jpjm1,1:jpkm1) = rn_avt0 * wmask(2:jpim1,2:jpjm1,1:jpkm1) 
    290328!!gm         avm(2:jpim1,2:jpjm1,1:jpkm1) = rn_avm0 * wmask(2:jpim1,2:jpjm1,1:jpkm1) 
    291       END SELECT 
     329         END SELECT 
     330 
     331         IF( ln_tile .AND. .NOT. l_istiled ) CALL dom_tile_start( ldhold=.TRUE. ) 
     332      ENDIF 
    292333      ! 
    293334      !                          !==  ocean Kz  ==!   (avt, avs, avm) 
    294335      ! 
    295336      !                                         !* start from turbulent closure values 
    296       avt(:,:,2:jpkm1) = avt_k(:,:,2:jpkm1) 
    297       avm(:,:,2:jpkm1) = avm_k(:,:,2:jpkm1) 
     337      DO_3D_OVR( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 ) 
     338         avt(ji,jj,jk) = avt_k(ji,jj,jk) 
     339         avm(ji,jj,jk) = avm_k(ji,jj,jk) 
     340      END_3D 
    298341      ! 
    299342      IF( ln_rnf_mouth ) THEN                   !* increase diffusivity at rivers mouths 
    300          DO jk = 2, nkrnf 
    301             avt(:,:,jk) = avt(:,:,jk) + 2._wp * rn_avt_rnf * rnfmsk(:,:) * wmask(:,:,jk) 
    302          END DO 
     343         DO_3D_OVR( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, nkrnf ) 
     344            avt(ji,jj,jk) = avt(ji,jj,jk) + 2._wp * rn_avt_rnf * rnfmsk(ji,jj) * wmask(ji,jj,jk) 
     345         END_3D 
    303346      ENDIF 
    304347      ! 
     
    309352                        CALL zdf_ddm( kt, Kmm,  avm, avt, avs ) 
    310353      ELSE                                            ! same mixing on all tracers 
    311          avs(2:jpim1,2:jpjm1,1:jpkm1) = avt(2:jpim1,2:jpjm1,1:jpkm1) 
     354         DO_3D_OVR( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 1, jpkm1 ) 
     355            avs(ji,jj,jk) = avt(ji,jj,jk) 
     356         END_3D 
    312357      ENDIF 
    313358      ! 
     
    318363#if defined key_agrif 
    319364      ! interpolation parent grid => child grid for avm_k ( ex : at west border: update column 1 and 2) 
    320       IF( l_zdfsh2 )   CALL Agrif_avm 
     365      IF( .NOT. l_istiled .OR. ntile == nijtile ) THEN                       ! Do only on the last tile 
     366         IF( l_zdfsh2 )   CALL Agrif_avm 
     367      ENDIF 
    321368#endif 
    322369 
    323370      !                                         !* Lateral boundary conditions (sign unchanged) 
    324       IF(nn_hls==1) THEN  
     371      IF(nn_hls==1) THEN 
    325372         IF( l_zdfsh2 ) THEN 
    326373            CALL lbc_lnk( 'zdfphy', avm_k, 'W', 1.0_wp , avt_k, 'W', 1.0_wp,   & 
    327                &                    avm  , 'W', 1.0_wp , avt  , 'W', 1.0_wp , avs , 'W', 1.0_wp ) 
     374                  &                 avm  , 'W', 1.0_wp , avt  , 'W', 1.0_wp , avs , 'W', 1.0_wp ) 
    328375         ELSE 
    329376            CALL lbc_lnk( 'zdfphy', avm  , 'W', 1.0_wp , avt  , 'W', 1.0_wp , avs , 'W', 1.0_wp ) 
    330377         ENDIF 
    331       ! 
     378         ! 
    332379         IF( l_zdfdrg ) THEN     ! drag  have been updated (non-linear cases) 
    333380            IF( ln_isfcav ) THEN   ;  CALL lbc_lnk( 'zdfphy', rCdU_top, 'T', 1.0_wp , rCdU_bot, 'T', 1.0_wp )   ! top & bot drag 
    334             ELSE                   ;  CALL lbc_lnk( 'zdfphy', rCdU_bot, 'T', 1.0_wp )                       ! bottom drag only 
     381            ELSE                   ;  CALL lbc_lnk( 'zdfphy', rCdU_bot, 'T', 1.0_wp )                           ! bottom drag only 
    335382            ENDIF 
    336383         ENDIF 
    337384      ENDIF 
    338385      ! 
    339       CALL zdf_mxl( kt, Kmm )                        !* mixed layer depth, and level 
    340       ! 
    341       IF( lrst_oce ) THEN                       !* write TKE, GLS or RIC fields in the restart file 
    342          IF( ln_zdftke )   CALL tke_rst( kt, 'WRITE' ) 
    343          IF( ln_zdfgls )   CALL gls_rst( kt, 'WRITE' ) 
    344          IF( ln_zdfric )   CALL ric_rst( kt, 'WRITE' ) 
    345          ! NB. OSMOSIS restart (osm_rst) will be called in step.F90 after ww has been updated 
     386      CALL zdf_mxl_turb( kt, Kmm )                   !* turbocline depth 
     387      ! 
     388      IF( .NOT. l_istiled .OR. ntile == nijtile ) THEN                       ! Do only on the last tile 
     389         IF( lrst_oce ) THEN                       !* write TKE, GLS or RIC fields in the restart file 
     390            IF( ln_zdftke )   CALL tke_rst( kt, 'WRITE' ) 
     391            IF( ln_zdfgls )   CALL gls_rst( kt, 'WRITE' ) 
     392            IF( ln_zdfric )   CALL ric_rst( kt, 'WRITE' ) 
     393            ! NB. OSMOSIS restart (osm_rst) will be called in step.F90 after ww has been updated 
     394         ENDIF 
    346395      ENDIF 
    347396      ! 
Note: See TracChangeset for help on using the changeset viewer.