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 15556 for NEMO/trunk/src/OCE/DOM/domzgr.F90 – NEMO

Ignore:
Timestamp:
2021-11-29T16:23:06+01:00 (2 years ago)
Author:
jchanut
Message:

#2638: Add the possibility to read bottom levels at U/V/F points in the mesh file. Store fe3mask (i.e. fmask as it is prior updating it for lateral boundary conditions). All is this is only needed to ensure a correct update of parent grid variables with AgRIF. This also anticipates the possible use of coarsened meshes.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/src/OCE/DOM/domzgr.F90

    r15529 r15556  
    7474      INTEGER  ::   ikt, ikb            ! top/bot index 
    7575      INTEGER  ::   ioptio, ibat, ios   ! local integer 
     76      INTEGER  ::   is_mbkuvf           ! ==0 if mbku, mbkv, mbkf to be computed 
    7677      REAL(wp) ::   zrefdep             ! depth of the reference level (~10m) 
    7778      REAL(wp), DIMENSION(jpi,jpj  ) ::   zmsk 
     
    9798            &              e3t_0   , e3u_0   , e3v_0 , e3f_0    ,   &    ! vertical scale factors 
    9899            &              e3w_0   , e3uw_0  , e3vw_0           ,   &    ! vertical scale factors 
    99             &              k_top   , k_bot            )                  ! 1st & last ocean level 
     100            &              k_top   , k_bot                      ,   &    ! 1st & last ocean level 
     101            &              is_mbkuvf, mbku, mbkv, mbkf )                 ! U/V/F points bottom levels 
    100102            ! 
    101103      ELSE                          !==  User defined configuration  ==! 
    102104         IF(lwp) WRITE(numout,*) 
    103105         IF(lwp) WRITE(numout,*) '          User defined vertical mesh (usr_def_zgr)' 
     106         is_mbkuvf = 0 
    104107         ! 
    105108         CALL usr_def_zgr( ln_zco  , ln_zps  , ln_sco, ln_isfcav,   &  
     
    177180 
    178181      !                                ! top/bottom ocean level indices for t-, u- and v-points (f-point also for top) 
    179       CALL zgr_top_bot( k_top, k_bot )      ! with a minimum value set to 1 
     182      CALL zgr_top_bot( k_top, k_bot, is_mbkuvf )      ! with a minimum value set to 1 
    180183      ! 
    181184      !                                ! ice shelf draft and bathymetry 
     
    220223      &                 pe3t  , pe3u  , pe3v   , pe3f ,            &   ! vertical scale factors 
    221224      &                 pe3w  , pe3uw , pe3vw         ,            &   !     -      -      - 
    222       &                 k_top  , k_bot    )                            ! top & bottom ocean level 
     225      &                 k_top  , k_bot  ,                          &   ! top & bottom ocean level 
     226      &                 k_mbkuvf  , k_bot_u  , k_bot_v  , k_bot_f  )   ! U/V/F points bottom levels 
    223227      !!--------------------------------------------------------------------- 
    224228      !!              ***  ROUTINE zgr_read  *** 
     
    235239      REAL(wp), DIMENSION(:,:,:), INTENT(out) ::   pe3w , pe3uw, pe3vw         !    -       -      - 
    236240      INTEGER , DIMENSION(:,:)  , INTENT(out) ::   k_top , k_bot               ! first & last ocean level 
     241      INTEGER                   , INTENT(out) ::   k_mbkuvf                    ! ==1 if mbku, mbkv, mbkf are in file 
     242      INTEGER , DIMENSION(:,:)  , INTENT(out) ::   k_bot_u , k_bot_v, k_bot_f  ! bottom levels at U/V/F points 
    237243      ! 
    238244      INTEGER  ::   ji,jj,jk     ! dummy loop index 
     
    322328      ENDIF 
    323329      ! 
     330      IF( iom_varid( inum, 'mbku', ldstop = .FALSE. ) > 0 ) THEN 
     331         IF(lwp) WRITE(numout,*) '          mbku, mbkv & mbkf read in ', TRIM(cn_domcfg), ' file' 
     332         CALL iom_get( inum, jpdom_global, 'mbku', z2d ) 
     333         k_bot_u(:,:) = NINT( z2d(:,:) ) 
     334         CALL iom_get( inum, jpdom_global, 'mbkv', z2d ) 
     335         k_bot_v(:,:) = NINT( z2d(:,:) ) 
     336         CALL iom_get( inum, jpdom_global, 'mbkf', z2d ) 
     337         k_bot_f(:,:) = NINT( z2d(:,:) ) 
     338         k_mbkuvf = 1 
     339      ELSE 
     340         k_mbkuvf = 0 
     341      ENDIF 
     342      ! 
    324343      ! reference depth for negative bathy (wetting and drying only) 
    325344      IF( ll_wd )  CALL iom_get( inum,  'rn_wd_ref_depth' , ssh_ref   ) 
     
    330349 
    331350 
    332    SUBROUTINE zgr_top_bot( k_top, k_bot ) 
     351   SUBROUTINE zgr_top_bot( k_top, k_bot, k_mbkuvf ) 
    333352      !!---------------------------------------------------------------------- 
    334353      !!                    ***  ROUTINE zgr_top_bot  *** 
     
    342361      !!                                     (min value = 1) 
    343362      !! ** Action  :   mbkt, mbku, mbkv :   vertical indices of the deeptest  
    344       !!                                     ocean level at t-, u- & v-points 
     363      !!                mbkf                 ocean level at t-, u-, v- & f-points 
    345364      !!                                     (min value = 1 over land) 
    346365      !!---------------------------------------------------------------------- 
    347366      INTEGER , DIMENSION(:,:), INTENT(in) ::   k_top, k_bot   ! top & bottom ocean level indices 
     367      INTEGER                 , INTENT(in) ::   k_mbkuvf       ! flag to recompute mbku, mbkv, mbkf 
    348368      ! 
    349369      INTEGER ::   ji, jj   ! dummy loop indices 
     
    365385         mikv(ji,jj) = MAX(  mikt(ji  ,jj+1) , mikt(ji,jj)  ) 
    366386         mikf(ji,jj) = MAX(  mikt(ji  ,jj+1) , mikt(ji,jj), mikt(ji+1,jj  ), mikt(ji+1,jj+1)  ) 
    367          ! 
    368          mbku(ji,jj) = MIN(  mbkt(ji+1,jj  ) , mbkt(ji,jj)  ) 
    369          mbkv(ji,jj) = MIN(  mbkt(ji  ,jj+1) , mbkt(ji,jj)  ) 
    370       END_2D 
    371       ! converte into REAL to use lbc_lnk ; impose a min value of 1 as a zero can be set in lbclnk  
     387      END_2D 
     388 
     389      IF ( k_mbkuvf==0 ) THEN 
     390         IF(lwp) WRITE(numout,*) '         mbku, mbkv, mbkf computed from mbkt' 
     391         DO_2D( 0, 0, 0, 0 ) 
     392            mbku(ji,jj) = MIN(  mbkt(ji+1,jj  ) , mbkt(ji,jj)  ) 
     393            mbkv(ji,jj) = MIN(  mbkt(ji  ,jj+1) , mbkt(ji,jj)  ) 
     394            mbkf(ji,jj) = MIN(  mbkt(ji  ,jj+1) , mbkt(ji,jj), mbkt(ji+1,jj  ), mbkt(ji+1,jj+1)  ) 
     395         END_2D 
     396      ELSE 
     397         IF(lwp) WRITE(numout,*) '         mbku, mbkv, mbkf read from file' 
     398         ! Use mbku, mbkv, mbkf from file 
     399         ! Ensure these are lower than expected bottom level deduced from mbkt 
     400         DO_2D( 0, 0, 0, 0 ) 
     401            mbku(ji,jj) = MIN(  mbku(ji,jj), mbkt(ji+1,jj  ) , mbkt(ji,jj)  ) 
     402            mbkv(ji,jj) = MIN(  mbkv(ji,jj), mbkt(ji  ,jj+1) , mbkt(ji,jj)  ) 
     403            mbkf(ji,jj) = MIN(  mbkf(ji,jj), mbkt(ji  ,jj+1) , mbkt(ji,jj), mbkt(ji+1,jj  ), mbkt(ji+1,jj+1)  ) 
     404         END_2D 
     405      ENDIF 
     406      ! convert into REAL to use lbc_lnk ; impose a min value of 1 as a zero can be set in lbclnk  
    372407      DO_2D( 0, 0, 0, 0 ) 
    373408         zk(ji,jj) = REAL( miku(ji,jj), wp ) 
     
    399434      CALL lbc_lnk( 'domzgr', zk, 'V', 1.0_wp ) 
    400435      mbkv(:,:) = MAX( NINT( zk(:,:) ), 1 ) 
     436 
     437      DO_2D( 0, 0, 0, 0 ) 
     438         zk(ji,jj) = REAL( mbkf(ji,jj), wp ) 
     439      END_2D 
     440      CALL lbc_lnk( 'domzgr', zk, 'F', 1.0_wp ) 
     441      mbkf(:,:) = MAX( NINT( zk(:,:) ), 1 ) 
    401442      ! 
    402443   END SUBROUTINE zgr_top_bot 
Note: See TracChangeset for help on using the changeset viewer.