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 14037 for NEMO/branches/2020/dev_r13333_KERNEL-08_techene_gm_HPG_SPG/src/OCE/TRA/tramle.F90 – NEMO

Ignore:
Timestamp:
2020-12-03T12:20:38+01:00 (3 years ago)
Author:
ayoung
Message:

Updated to trunk at 14020. Sette tests passed with change of results for configurations with non-linear ssh. Ticket #2506.

Location:
NEMO/branches/2020/dev_r13333_KERNEL-08_techene_gm_HPG_SPG
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_r13333_KERNEL-08_techene_gm_HPG_SPG

    • Property svn:externals
      •  

        old new  
        88 
        99# SETTE 
        10 ^/utils/CI/sette@13292        sette 
         10^/utils/CI/sette_wave@13990         sette 
  • NEMO/branches/2020/dev_r13333_KERNEL-08_techene_gm_HPG_SPG/src/OCE/TRA/tramle.F90

    r13295 r14037  
    7979      !!             Fox-Kemper and Ferrari, JPO, 38, 1166-1179, 2008 
    8080      !!---------------------------------------------------------------------- 
    81       INTEGER                         , INTENT(in   ) ::   kt         ! ocean time-step index 
    82       INTEGER                         , INTENT(in   ) ::   kit000     ! first time step index 
    83       INTEGER                         , INTENT(in   ) ::   Kmm        ! ocean time level index 
    84       CHARACTER(len=3)                , INTENT(in   ) ::   cdtype     ! =TRA or TRC (tracer indicator) 
    85       REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   pu         ! in : 3 ocean transport components 
    86       REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   pv         ! out: same 3  transport components 
    87       REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   pw         !   increased by the MLE induced transport 
     81      INTEGER                     , INTENT(in   ) ::   kt         ! ocean time-step index 
     82      INTEGER                     , INTENT(in   ) ::   kit000     ! first time step index 
     83      INTEGER                     , INTENT(in   ) ::   Kmm        ! ocean time level index 
     84      CHARACTER(len=3)            , INTENT(in   ) ::   cdtype     ! =TRA or TRC (tracer indicator) 
     85      REAL(wp), DIMENSION(A2D(nn_hls),jpk), INTENT(inout) ::   pu         ! in : 3 ocean transport components 
     86      REAL(wp), DIMENSION(A2D(nn_hls),jpk), INTENT(inout) ::   pv         ! out: same 3  transport components 
     87      REAL(wp), DIMENSION(A2D(nn_hls),jpk), INTENT(inout) ::   pw         !   increased by the MLE induced transport 
    8888      ! 
    8989      INTEGER  ::   ji, jj, jk          ! dummy loop indices 
     
    9191      REAL(wp) ::   zcuw, zmuw, zc      ! local scalar 
    9292      REAL(wp) ::   zcvw, zmvw          !   -      - 
    93       INTEGER , DIMENSION(jpi,jpj)     :: inml_mle 
    94       REAL(wp), DIMENSION(jpi,jpj)     :: zpsim_u, zpsim_v, zmld, zbm, zhu, zhv, zn2, zLf_NH, zLf_MH 
    95       REAL(wp), DIMENSION(jpi,jpj,jpk) :: zpsi_uw, zpsi_vw 
     93      INTEGER , DIMENSION(A2D(nn_hls))     :: inml_mle 
     94      REAL(wp), DIMENSION(A2D(nn_hls))     :: zpsim_u, zpsim_v, zmld, zbm, zhu, zhv, zn2, zLf_MH 
     95      REAL(wp), DIMENSION(A2D(nn_hls),jpk) :: zpsi_uw, zpsi_vw 
     96      ! TEMP: [tiling] These changes not necessary if using XIOS (subdomain support) 
     97      REAL(wp), DIMENSION(:,:),   ALLOCATABLE, SAVE :: zLf_NH 
     98      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, SAVE :: zpsiu_mle, zpsiv_mle 
    9699      !!---------------------------------------------------------------------- 
    97100      ! 
    98101      !                                      !==  MLD used for MLE  ==! 
    99102      !                                                ! compute from the 10m density to deal with the diurnal cycle 
    100       inml_mle(:,:) = mbkt(:,:) + 1                    ! init. to number of ocean w-level (T-level + 1) 
     103      DO_2D( 1, 1, 1, 1 ) 
     104         inml_mle(ji,jj) = mbkt(ji,jj) + 1                    ! init. to number of ocean w-level (T-level + 1) 
     105      END_2D 
    101106      IF ( nla10 > 0 ) THEN                            ! avoid case where first level is thicker than 10m 
    102          DO_3DS( 1, 1, 1, 1, jpkm1, nlb10, -1 ) 
     107         DO_3DS( 1, 1, 1, 1, jpkm1, nlb10, -1 )        ! from the bottom to nlb10 (10m) 
    103108            IF( rhop(ji,jj,jk) > rhop(ji,jj,nla10) + rn_rho_c_mle )   inml_mle(ji,jj) = jk      ! Mixed layer 
    104109         END_3D 
     
    110115      zbm (:,:) = 0._wp 
    111116      zn2 (:,:) = 0._wp 
    112       DO_3D( 1, 1, 1, 1, 1, ikmax ) 
     117      DO_3D( 1, 1, 1, 1, 1, ikmax )                    ! MLD and mean buoyancy and N2 over the mixed layer 
    113118         zc = e3t(ji,jj,jk,Kmm) * REAL( MIN( MAX( 0, inml_mle(ji,jj)-jk ) , 1  )  )    ! zc being 0 outside the ML t-points 
    114119         zmld(ji,jj) = zmld(ji,jj) + zc 
     
    135140      END SELECT 
    136141      !                                                ! convert density into buoyancy 
    137       zbm(:,:) = + grav * zbm(:,:) / MAX( e3t(:,:,1,Kmm), zmld(:,:) ) 
     142      DO_2D( 1, 1, 1, 1 ) 
     143         zbm(ji,jj) = + grav * zbm(ji,jj) / MAX( e3t(ji,jj,1,Kmm), zmld(ji,jj) ) 
     144      END_2D 
    138145      ! 
    139146      ! 
     
    182189      zpsi_vw(:,:,:) = 0._wp 
    183190      ! 
    184       DO_3D( 1, 0, 1, 0, 2, ikmax ) 
     191      DO_3D( 1, 0, 1, 0, 2, ikmax )                ! start from 2 : surface value = 0 
    185192         zcuw = 1._wp - ( gdepw(ji+1,jj,jk,Kmm) + gdepw(ji,jj,jk,Kmm) ) * zhu(ji,jj) 
    186193         zcvw = 1._wp - ( gdepw(ji,jj+1,jk,Kmm) + gdepw(ji,jj,jk,Kmm) ) * zhv(ji,jj) 
     
    196203      !                                      !==  transport increased by the MLE induced transport ==! 
    197204      DO jk = 1, ikmax 
    198          DO_2D( 1, 0, 1, 0 ) 
     205         DO_2D( 1, 0, 1, 0 )                      ! CAUTION pu,pv must be defined at row/column i=1 / j=1 
    199206            pu(ji,jj,jk) = pu(ji,jj,jk) + ( zpsi_uw(ji,jj,jk) - zpsi_uw(ji,jj,jk+1) ) 
    200207            pv(ji,jj,jk) = pv(ji,jj,jk) + ( zpsi_vw(ji,jj,jk) - zpsi_vw(ji,jj,jk+1) ) 
     
    206213      END DO 
    207214 
     215      ! TEMP: [tiling] These changes not necessary if using XIOS (subdomain support) 
    208216      IF( cdtype == 'TRA') THEN              !==  outputs  ==! 
    209          ! 
    210          zLf_NH(:,:) = SQRT( rb_c * zmld(:,:) ) * r1_ft(:,:)      ! Lf = N H / f 
    211          CALL iom_put( "Lf_NHpf" , zLf_NH  )    ! Lf = N H / f 
     217         IF( ntile == 0 .OR. ntile == 1 ) THEN                             ! Do only on the first tile 
     218            ALLOCATE( zLf_NH(jpi,jpj), zpsiu_mle(jpi,jpj,jpk), zpsiv_mle(jpi,jpj,jpk) ) 
     219            zpsiu_mle(:,:,:) = 0._wp ; zpsiv_mle(:,:,:) = 0._wp 
     220         ENDIF 
     221         ! 
     222         DO_2D( 0, 0, 0, 0 ) 
     223            zLf_NH(ji,jj) = SQRT( rb_c * zmld(ji,jj) ) * r1_ft(ji,jj)      ! Lf = N H / f 
     224         END_2D 
    212225         ! 
    213226         ! divide by cross distance to give streamfunction with dimensions m^2/s 
    214          DO jk = 1, ikmax+1 
    215             zpsi_uw(:,:,jk) = zpsi_uw(:,:,jk) * r1_e2u(:,:) 
    216             zpsi_vw(:,:,jk) = zpsi_vw(:,:,jk) * r1_e1v(:,:) 
    217          END DO 
    218          CALL iom_put( "psiu_mle", zpsi_uw )    ! i-mle streamfunction 
    219          CALL iom_put( "psiv_mle", zpsi_vw )    ! j-mle streamfunction 
     227         DO_3D( 0, 0, 0, 0, 1, ikmax+1 ) 
     228            zpsiu_mle(ji,jj,jk) = zpsi_uw(ji,jj,jk) * r1_e2u(ji,jj) 
     229            zpsiv_mle(ji,jj,jk) = zpsi_vw(ji,jj,jk) * r1_e1v(ji,jj) 
     230         END_3D 
     231 
     232         IF( ntile == 0 .OR. ntile == nijtile ) THEN                       ! Do only on the last tile 
     233            CALL iom_put( "Lf_NHpf" , zLf_NH  )    ! Lf = N H / f 
     234            CALL iom_put( "psiu_mle", zpsiu_mle )    ! i-mle streamfunction 
     235            CALL iom_put( "psiv_mle", zpsiv_mle )    ! j-mle streamfunction 
     236            DEALLOCATE( zLf_NH, zpsiu_mle, zpsiv_mle ) 
     237         ENDIF 
    220238      ENDIF 
    221239      ! 
     
    283301            IF( ierr /= 0 )   CALL ctl_stop( 'tra_adv_mle_init: failed to allocate arrays' ) 
    284302            z1_t2 = 1._wp / ( rn_time * rn_time ) 
    285             DO_2D( 0, 1, 0, 1 ) 
     303            DO_2D( nn_hls-1, nn_hls, nn_hls-1, nn_hls )                      ! "coriolis+ time^-1" at u- & v-points 
    286304               zfu = ( ff_f(ji,jj) + ff_f(ji,jj-1) ) * 0.5_wp 
    287305               zfv = ( ff_f(ji,jj) + ff_f(ji-1,jj) ) * 0.5_wp 
     
    289307               rfv(ji,jj) = SQRT(  zfv * zfv + z1_t2 ) 
    290308            END_2D 
    291             CALL lbc_lnk_multi( 'tramle', rfu, 'U', 1.0_wp , rfv, 'V', 1.0_wp ) 
     309            IF (nn_hls.EQ.1) CALL lbc_lnk_multi( 'tramle', rfu, 'U', 1.0_wp , rfv, 'V', 1.0_wp ) 
    292310            ! 
    293311         ELSEIF( nn_mle == 1 ) THEN           ! MLE array allocation & initialisation 
Note: See TracChangeset for help on using the changeset viewer.