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 14958 for NEMO/branches/2021/dev_r14608_AGRIF_domcfg/src/OCE/TRA/tramle.F90 – NEMO

Ignore:
Timestamp:
2021-06-07T16:31:38+02:00 (3 years ago)
Author:
jchanut
Message:

#2638, synchronize branch with trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/dev_r14608_AGRIF_domcfg/src/OCE/TRA/tramle.F90

    r14433 r14958  
    8787      INTEGER                     , INTENT(in   ) ::   Kmm        ! ocean time level index 
    8888      CHARACTER(len=3)            , INTENT(in   ) ::   cdtype     ! =TRA or TRC (tracer indicator) 
    89       REAL(wp), DIMENSION(A2D(nn_hls),jpk), INTENT(inout) ::   pu         ! in : 3 ocean transport components 
    90       REAL(wp), DIMENSION(A2D(nn_hls),jpk), INTENT(inout) ::   pv         ! out: same 3  transport components 
    91       REAL(wp), DIMENSION(A2D(nn_hls),jpk), INTENT(inout) ::   pw         !   increased by the MLE induced transport 
     89      ! TEMP: [tiling] Can be A2D(nn_hls) after all lbc_lnks removed in the nn_hls = 2 case in tra_adv_fct 
     90      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   pu         ! in : 3 ocean transport components 
     91      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   pv         ! out: same 3  transport components 
     92      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   pw         !   increased by the MLE induced transport 
    9293      ! 
    9394      INTEGER  ::   ji, jj, jk          ! dummy loop indices 
     
    9697      REAL(wp) ::   zcvw, zmvw          !   -      - 
    9798      INTEGER , DIMENSION(A2D(nn_hls))     :: inml_mle 
    98       REAL(wp), DIMENSION(A2D(nn_hls))     :: zpsim_u, zpsim_v, zmld, zbm, zhu, zhv, zn2, zLf_MH 
     99      REAL(wp), DIMENSION(A2D(nn_hls))     :: zpsim_u, zpsim_v, zmld, zbm, zhu, zhv, zn2, zLf_NH, zLf_MH 
    99100      REAL(wp), DIMENSION(A2D(nn_hls),jpk) :: zpsi_uw, zpsi_vw 
    100       ! TEMP: [tiling] These changes not necessary if using XIOS (subdomain support) 
    101       REAL(wp), DIMENSION(:,:),   ALLOCATABLE, SAVE :: zLf_NH 
    102       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, SAVE :: zpsiu_mle, zpsiv_mle 
    103101      !!---------------------------------------------------------------------- 
    104102      ! 
     
    110108         SELECT CASE( nn_mld_uv )                         ! MLD at u- & v-pts 
    111109         CASE ( 0 )                                               != min of the 2 neighbour MLDs 
    112             DO_2D( 1, 0, 1, 0 ) 
     110            DO_2D( nn_hls, nn_hls-1, nn_hls, nn_hls-1 ) 
    113111               zhu(ji,jj) = MIN( hmle(ji+1,jj), hmle(ji,jj) ) 
    114112               zhv(ji,jj) = MIN( hmle(ji,jj+1), hmle(ji,jj) ) 
    115113            END_2D 
    116114         CASE ( 1 )                                               != average of the 2 neighbour MLDs 
    117             DO_2D( 1, 0, 1, 0 ) 
     115            DO_2D( nn_hls, nn_hls-1, nn_hls, nn_hls-1 ) 
    118116               zhu(ji,jj) = MAX( hmle(ji+1,jj), hmle(ji,jj) ) 
    119117               zhv(ji,jj) = MAX( hmle(ji,jj+1), hmle(ji,jj) ) 
    120118            END_2D 
    121119         CASE ( 2 )                                               != max of the 2 neighbour MLDs 
    122             DO_2D( 1, 0, 1, 0 ) 
     120            DO_2D( nn_hls, nn_hls-1, nn_hls, nn_hls-1 ) 
    123121               zhu(ji,jj) = MAX( hmle(ji+1,jj), hmle(ji,jj) ) 
    124122               zhv(ji,jj) = MAX( hmle(ji,jj+1), hmle(ji,jj) ) 
     
    126124         END SELECT 
    127125         IF( nn_mle == 0 ) THEN           ! Fox-Kemper et al. 2010 formulation 
    128             DO_2D( 1, 0, 1, 0 ) 
     126            DO_2D( nn_hls, nn_hls-1, nn_hls, nn_hls-1 ) 
    129127               zpsim_u(ji,jj) = rn_ce * zhu(ji,jj) * zhu(ji,jj)  * e2u(ji,jj)                                            & 
    130128                    &           * dbdx_mle(ji,jj) * MIN( 111.e3_wp , e1u(ji,jj) )   & 
     
    137135            ! 
    138136         ELSEIF( nn_mle == 1 ) THEN       ! New formulation (Lf = 5km fo/ff with fo=Coriolis parameter at latitude rn_lat) 
    139             DO_2D( 1, 0, 1, 0 ) 
     137            DO_2D( nn_hls, nn_hls-1, nn_hls, nn_hls-1 ) 
    140138               zpsim_u(ji,jj) = rc_f *   zhu(ji,jj)   * zhu(ji,jj)   * e2u(ji,jj)               & 
    141139                    &                  * dbdx_mle(ji,jj) * MIN( 111.e3_wp , e1u(ji,jj) ) 
     
    149147         !                                      !==  MLD used for MLE  ==! 
    150148         !                                                ! compute from the 10m density to deal with the diurnal cycle 
    151          DO_2D( 1, 1, 1, 1 ) 
     149         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    152150            inml_mle(ji,jj) = mbkt(ji,jj) + 1                    ! init. to number of ocean w-level (T-level + 1) 
    153151         END_2D 
    154152         IF ( nla10 > 0 ) THEN                            ! avoid case where first level is thicker than 10m 
    155            DO_3DS( 1, 1, 1, 1, jpkm1, nlb10, -1 )        ! from the bottom to nlb10 (10m) 
     153           DO_3DS( nn_hls, nn_hls, nn_hls, nn_hls, jpkm1, nlb10, -1 )        ! from the bottom to nlb10 (10m) 
    156154              IF( rhop(ji,jj,jk) > rhop(ji,jj,nla10) + rn_rho_c_mle )   inml_mle(ji,jj) = jk      ! Mixed layer 
    157155           END_3D 
     
    163161         zbm (:,:) = 0._wp 
    164162         zn2 (:,:) = 0._wp 
    165          DO_3D( 1, 1, 1, 1, 1, ikmax )                    ! MLD and mean buoyancy and N2 over the mixed layer 
     163         DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, ikmax )                    ! MLD and mean buoyancy and N2 over the mixed layer 
    166164            zc = e3t(ji,jj,jk,Kmm) * REAL( MIN( MAX( 0, inml_mle(ji,jj)-jk ) , 1  )  )    ! zc being 0 outside the ML t-points 
    167165            zmld(ji,jj) = zmld(ji,jj) + zc 
     
    172170         SELECT CASE( nn_mld_uv )                         ! MLD at u- & v-pts 
    173171         CASE ( 0 )                                               != min of the 2 neighbour MLDs 
    174             DO_2D( 1, 0, 1, 0 ) 
     172            DO_2D( nn_hls, nn_hls-1, nn_hls, nn_hls-1 ) 
    175173               zhu(ji,jj) = MIN( zmld(ji+1,jj), zmld(ji,jj) ) 
    176174               zhv(ji,jj) = MIN( zmld(ji,jj+1), zmld(ji,jj) ) 
    177175            END_2D 
    178176         CASE ( 1 )                                               != average of the 2 neighbour MLDs 
    179             DO_2D( 1, 0, 1, 0 ) 
     177            DO_2D( nn_hls, nn_hls-1, nn_hls, nn_hls-1 ) 
    180178               zhu(ji,jj) = ( zmld(ji+1,jj) + zmld(ji,jj) ) * 0.5_wp 
    181179               zhv(ji,jj) = ( zmld(ji,jj+1) + zmld(ji,jj) ) * 0.5_wp 
    182180            END_2D 
    183181         CASE ( 2 )                                               != max of the 2 neighbour MLDs 
    184             DO_2D( 1, 0, 1, 0 ) 
     182            DO_2D( nn_hls, nn_hls-1, nn_hls, nn_hls-1 ) 
    185183               zhu(ji,jj) = MAX( zmld(ji+1,jj), zmld(ji,jj) ) 
    186184               zhv(ji,jj) = MAX( zmld(ji,jj+1), zmld(ji,jj) ) 
     
    188186         END SELECT 
    189187         !                                                ! convert density into buoyancy 
    190          DO_2D( 1, 1, 1, 1 ) 
     188         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    191189            zbm(ji,jj) = + grav * zbm(ji,jj) / MAX( e3t(ji,jj,1,Kmm), zmld(ji,jj) ) 
    192190         END_2D 
     
    201199         ! 
    202200         IF( nn_mle == 0 ) THEN           ! Fox-Kemper et al. 2010 formulation 
    203             DO_2D( 1, 0, 1, 0 ) 
     201            DO_2D( nn_hls, nn_hls-1, nn_hls, nn_hls-1 ) 
    204202               zpsim_u(ji,jj) = rn_ce * zhu(ji,jj) * zhu(ji,jj)  * e2_e1u(ji,jj)                                            & 
    205203                    &           * ( zbm(ji+1,jj) - zbm(ji,jj) ) * MIN( 111.e3_wp , e1u(ji,jj) )   & 
     
    212210            ! 
    213211         ELSEIF( nn_mle == 1 ) THEN       ! New formulation (Lf = 5km fo/ff with fo=Coriolis parameter at latitude rn_lat) 
    214             DO_2D( 1, 0, 1, 0 ) 
     212            DO_2D( nn_hls, nn_hls-1, nn_hls, nn_hls-1 ) 
    215213               zpsim_u(ji,jj) = rc_f *   zhu(ji,jj)   * zhu(ji,jj)   * e2_e1u(ji,jj)               & 
    216214                    &                  * ( zbm(ji+1,jj) - zbm(ji,jj) ) * MIN( 111.e3_wp , e1u(ji,jj) ) 
     
    222220         ! 
    223221         IF( nn_conv == 1 ) THEN              ! No MLE in case of convection 
    224             DO_2D( 1, 0, 1, 0 ) 
     222            DO_2D( nn_hls, nn_hls-1, nn_hls, nn_hls-1 ) 
    225223               IF( MIN( zn2(ji,jj) , zn2(ji+1,jj) ) < 0._wp )   zpsim_u(ji,jj) = 0._wp 
    226224               IF( MIN( zn2(ji,jj) , zn2(ji,jj+1) ) < 0._wp )   zpsim_v(ji,jj) = 0._wp 
     
    230228      ENDIF  ! end of ln_osm_mle conditional 
    231229    !                                      !==  structure function value at uw- and vw-points  ==! 
    232     DO_2D( 1, 0, 1, 0 ) 
     230    DO_2D( nn_hls, nn_hls-1, nn_hls, nn_hls-1 ) 
    233231       zhu(ji,jj) = 1._wp / MAX(zhu(ji,jj), rsmall)                   ! hu --> 1/hu 
    234232       zhv(ji,jj) = 1._wp / MAX(zhv(ji,jj), rsmall)  
     
    238236    zpsi_vw(:,:,:) = 0._wp 
    239237    ! 
    240       DO_3D( 1, 0, 1, 0, 2, ikmax )                ! start from 2 : surface value = 0 
     238      DO_3D( nn_hls, nn_hls-1, nn_hls, nn_hls-1, 2, ikmax )                ! start from 2 : surface value = 0 
     239       
    241240         zcuw = 1._wp - ( gdepw(ji+1,jj,jk,Kmm) + gdepw(ji,jj,jk,Kmm) ) * zhu(ji,jj) 
    242241         zcvw = 1._wp - ( gdepw(ji,jj+1,jk,Kmm) + gdepw(ji,jj,jk,Kmm) ) * zhv(ji,jj) 
     
    252251      !                                      !==  transport increased by the MLE induced transport ==! 
    253252      DO jk = 1, ikmax 
    254          DO_2D( 1, 0, 1, 0 )                      ! CAUTION pu,pv must be defined at row/column i=1 / j=1 
     253         DO_2D_OVR( nn_hls, nn_hls-1, nn_hls, nn_hls-1 ) 
    255254            pu(ji,jj,jk) = pu(ji,jj,jk) + ( zpsi_uw(ji,jj,jk) - zpsi_uw(ji,jj,jk+1) ) 
    256255            pv(ji,jj,jk) = pv(ji,jj,jk) + ( zpsi_vw(ji,jj,jk) - zpsi_vw(ji,jj,jk+1) ) 
    257256         END_2D 
    258          DO_2D( 0, 0, 0, 0 ) 
     257         DO_2D_OVR( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1 ) 
    259258            pw(ji,jj,jk) = pw(ji,jj,jk) - ( zpsi_uw(ji,jj,jk) - zpsi_uw(ji-1,jj,jk)   & 
    260259               &                          + zpsi_vw(ji,jj,jk) - zpsi_vw(ji,jj-1,jk) ) * wmask(ji,jj,1) 
     
    262261      END DO 
    263262 
    264       ! TEMP: [tiling] These changes not necessary if using XIOS (subdomain support) 
    265263      IF( cdtype == 'TRA') THEN              !==  outputs  ==! 
    266          IF( ntile == 0 .OR. ntile == 1 ) THEN                             ! Do only on the first tile 
    267             ALLOCATE( zLf_NH(jpi,jpj), zpsiu_mle(jpi,jpj,jpk), zpsiv_mle(jpi,jpj,jpk) ) 
    268             zpsiu_mle(:,:,:) = 0._wp ; zpsiv_mle(:,:,:) = 0._wp 
    269          ENDIF 
    270264         ! 
    271265         IF (ln_osm_mle.and.ln_zdfosm) THEN 
     
    279273         ENDIF 
    280274         ! 
     275         CALL iom_put( "Lf_NHpf" , zLf_NH  )    ! Lf = N H / f 
     276         ! 
    281277         ! divide by cross distance to give streamfunction with dimensions m^2/s 
    282278         DO_3D( 0, 0, 0, 0, 1, ikmax+1 ) 
    283             zpsiu_mle(ji,jj,jk) = zpsi_uw(ji,jj,jk) * r1_e2u(ji,jj) 
    284             zpsiv_mle(ji,jj,jk) = zpsi_vw(ji,jj,jk) * r1_e1v(ji,jj) 
     279            zpsi_uw(ji,jj,jk) = zpsi_uw(ji,jj,jk) * r1_e2u(ji,jj) 
     280            zpsi_vw(ji,jj,jk) = zpsi_vw(ji,jj,jk) * r1_e1v(ji,jj) 
    285281         END_3D 
    286  
    287          IF( ntile == 0 .OR. ntile == nijtile ) THEN                       ! Do only on the last tile 
    288             CALL iom_put( "Lf_NHpf" , zLf_NH  )    ! Lf = N H / f 
    289             CALL iom_put( "psiu_mle", zpsiu_mle )    ! i-mle streamfunction 
    290             CALL iom_put( "psiv_mle", zpsiv_mle )    ! j-mle streamfunction 
    291             DEALLOCATE( zLf_NH, zpsiu_mle, zpsiv_mle ) 
    292          ENDIF 
     282         CALL iom_put( "psiu_mle", zpsi_uw )    ! i-mle streamfunction 
     283         CALL iom_put( "psiv_mle", zpsi_vw )    ! j-mle streamfunction 
    293284      ENDIF 
    294285      ! 
Note: See TracChangeset for help on using the changeset viewer.