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 13696 for NEMO/branches/2020/dev_r13327_KERNEL-06_2_techene_e3/src/OCE/DYN/dynspg_ts.F90 – NEMO

Ignore:
Timestamp:
2020-10-28T19:09:27+01:00 (3 years ago)
Author:
techene
Message:

#2555 use same e3f definition as in EEN in ENS and ENE instead of previous ugly fix and change time splitting accordingly change namelist vorticity scheme param nn_een_e3f into nn_e3f_typ

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_r13327_KERNEL-06_2_techene_e3/src/OCE/DYN/dynspg_ts.F90

    r13427 r13696  
    11191119      !! although they should be updated in the variable volume case. Not a big approximation. 
    11201120      !! To remove this approximation, copy lines below inside barotropic loop 
    1121       !! and update depths at T-F points (ht and zhf resp.) at each barotropic time step 
     1121      !! and update depths at T- points (ht) at each barotropic time step 
    11221122      !! 
    11231123      !! Compute zwz = f / ( height of the water colomn ) 
     
    11261126      INTEGER  ::   ji ,jj, jk              ! dummy loop indices 
    11271127      REAL(wp) ::   z1_ht 
    1128       REAL(wp), DIMENSION(jpi,jpj) :: zhf 
    11291128      !!---------------------------------------------------------------------- 
    11301129      ! 
    11311130      SELECT CASE( nvor_scheme ) 
    1132       CASE( np_EEN )                != EEN scheme using e3f energy & enstrophy scheme 
    1133          SELECT CASE( nn_een_e3f )              !* ff_f/e3 at F-point 
     1131      CASE( np_EEN, np_ENE, np_ENS , np_MIX )   !=  schemes using the same e3f definition 
     1132         SELECT CASE( nn_e3f_typ )                  !* ff_f/e3 at F-point 
    11341133         CASE ( 0 )                                   ! original formulation  (masked averaging of e3t divided by 4) 
    1135             DO_2D( 1, 0, 1, 0 ) 
     1134            DO_2D( 0, 0, 0, 0 ) 
    11361135               zwz(ji,jj) = ( ht(ji,jj+1) + ht(ji+1,jj+1)   & 
    11371136                    &       + ht(ji,jj  ) + ht(ji+1,jj  ) ) * 0.25_wp   
     
    11391138            END_2D 
    11401139         CASE ( 1 )                                   ! new formulation  (masked averaging of e3t divided by the sum of mask) 
    1141             DO_2D( 1, 0, 1, 0 ) 
     1140            DO_2D( 0, 0, 0, 0 ) 
    11421141               zwz(ji,jj) =     (    ht(ji,jj+1) +     ht(ji+1,jj+1)      & 
    11431142                    &            +   ht(ji,jj  ) +     ht(ji+1,jj  )  )   & 
     
    11481147         END SELECT 
    11491148         CALL lbc_lnk( 'dynspg_ts', zwz, 'F', 1._wp ) 
     1149      END SELECT 
     1150      ! 
     1151      SELECT CASE( nvor_scheme ) 
     1152      CASE( np_EEN ) 
    11501153         ! 
    11511154         ftne(1,:) = 0._wp   ;   ftnw(1,:) = 0._wp   ;   ftse(1,:) = 0._wp   ;   ftsw(1,:) = 0._wp 
     
    11571160         END_2D 
    11581161         ! 
    1159       CASE( np_EET )                  != EEN scheme using e3t energy conserving scheme 
     1162      CASE( np_EET )                            != EEN scheme using e3t energy conserving scheme 
    11601163         ftne(1,:) = 0._wp   ;   ftnw(1,:) = 0._wp   ;   ftse(1,:) = 0._wp   ;   ftsw(1,:) = 0._wp 
    11611164         DO_2D( 0, 1, 0, 1 ) 
     
    11671170         END_2D 
    11681171         ! 
    1169       CASE( np_ENE, np_ENS , np_MIX )  != all other schemes (ENE, ENS, MIX) except ENT ! 
    1170          ! 
    1171          zwz(:,:) = 0._wp 
    1172          zhf(:,:) = 0._wp 
    1173           
    1174          !!gm  assume 0 in both cases (which is almost surely WRONG ! ) as hvatf has been removed  
    1175 !!gm    A priori a better value should be something like : 
    1176 !!gm          zhf(i,j) = masked sum of  ht(i,j) , ht(i+1,j) , ht(i,j+1) , (i+1,j+1)  
    1177 !!gm                     divided by the sum of the corresponding mask  
    1178 !!gm  
    1179 !!             
    1180          IF( .NOT.ln_sco ) THEN 
    1181    
    1182    !!gm  agree the JC comment  : this should be done in a much clear way 
    1183    
    1184    ! JC: It not clear yet what should be the depth at f-points over land in z-coordinate case 
    1185    !     Set it to zero for the time being  
    1186    !              IF( rn_hmin < 0._wp ) THEN    ;   jk = - INT( rn_hmin )                                      ! from a nb of level 
    1187    !              ELSE                          ;   jk = MINLOC( gdepw_0, mask = gdepw_0 > rn_hmin, dim = 1 )  ! from a depth 
    1188    !              ENDIF 
    1189    !              zhf(:,:) = gdepw_0(:,:,jk+1) 
    1190             ! 
    1191          ELSE 
    1192             ! 
    1193             !zhf(:,:) = hbatf(:,:) 
    1194             DO_2D( 1, 0, 1, 0 ) 
    1195                zhf(ji,jj) =    (   ht_0  (ji,jj  ) + ht_0  (ji+1,jj  )          & 
    1196                     &            + ht_0  (ji,jj+1) + ht_0  (ji+1,jj+1)   )      & 
    1197                     &     / MAX(   ssmask(ji,jj  ) + ssmask(ji+1,jj  )          & 
    1198                     &            + ssmask(ji,jj+1) + ssmask(ji+1,jj+1) , 1._wp  ) 
    1199             END_2D 
    1200          ENDIF 
    1201          ! 
    1202          DO jj = 1, jpjm1   ! keep only the value at the coast if sco 
    1203             zhf(:,jj) = zhf(:,jj) * (1._wp- umask(:,jj,1) * umask(:,jj+1,1)) 
    1204          END DO 
    1205          ! 
    1206          DO jk = 1, jpkm1   ! ocean point : sum of masked e3f 
    1207             DO jj = 1, jpjm1 
    1208                zhf(:,jj) = zhf(:,jj) + e3f(:,jj,jk) * umask(:,jj,jk) * umask(:,jj+1,jk) 
    1209             END DO 
    1210          END DO 
    1211          CALL lbc_lnk( 'dynspg_ts', zhf, 'F', 1._wp ) 
    1212          ! JC: TBC. hf should be greater than 0  
    1213          DO_2D( 1, 1, 1, 1 ) 
    1214             IF( zhf(ji,jj) /= 0._wp )   zwz(ji,jj) = 1._wp / zhf(ji,jj) 
    1215          END_2D 
    1216          zwz(:,:) = ff_f(:,:) * zwz(:,:) 
    12171172      END SELECT 
    12181173       
    12191174   END SUBROUTINE dyn_cor_2d_init 
    1220  
    12211175 
    12221176 
     
    14121366   END SUBROUTINE wad_spg 
    14131367      
    1414  
    14151368 
    14161369   SUBROUTINE dyn_drg_init( Kbb, Kmm, puu, pvv, puu_b ,pvv_b, pu_RHSi, pv_RHSi, pCdU_u, pCdU_v ) 
Note: See TracChangeset for help on using the changeset viewer.