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 15279 for utils/tools/DOMAINcfg/src/domzgr.F90 – NEMO

Ignore:
Timestamp:
2021-09-23T12:00:23+02:00 (3 years ago)
Author:
jchanut
Message:

#2222 and #2638: Enable creating agrif meshes with different vertical grids (geopotential only as a start)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • utils/tools/DOMAINcfg/src/domzgr.F90

    r14952 r15279  
    4545   USE dombat 
    4646   USE domisf 
     47   USE agrif_connect 
    4748   USE agrif_domzgr 
    4849 
     
    176177      IF ( ln_sco .AND. ln_isfcav ) ioptio = ioptio + 1 
    177178      IF( ioptio > 0 )   CALL ctl_stop( ' Cavity not tested/compatible with full step (zco) and sigma (ln_sco) ' ) 
     179 
     180#if defined key_agrif 
     181!      IF ( (.NOT.Agrif_Root()).AND.((.NOT.ln_zps).OR.(.NOT.Agrif_parent(ln_zps)))) THEN 
     182!         CALL ctl_stop( 'STOP', 'AGRIF zooms require ln_zps=T for both Child and Parent') 
     183!      ENDIF 
     184#endif 
    178185 
    179186      IF(.NOT.ln_read_cfg) THEN 
     
    560567      REAL(wp) ::   r_bump , h_bump , h_oce   ! bump characteristics  
    561568      REAL(wp) ::   zi, zj, zh, zhmin         ! local scalars 
    562       REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   zrand  
     569      REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   zrand, zbatv  
    563570      !!---------------------------------------------------------------------- 
    564571      ! 
     
    609616            ENDIF 
    610617            IF ( cp_cfg=='DOME' ) THEN 
    611                bathy(:,:) = MIN(3600._wp, MAX( 600._wp,  600._wp -gphit(:,:)*1.e3*0.01 )) 
     618               ALLOCATE(zbatv(jpi,jpj)) 
     619               zbatv(:,:) = MIN(3600._wp, MAX( 600._wp,  600._wp -gphiv(:,:)*1.e3*0.01 )) 
     620               bathy(:,1) = 0._wp 
     621               DO jj =2,jpj 
     622                  bathy(:,jj) = 0.5_wp*(zbatv(:,jj) + zbatv(:,jj-1)) 
     623               END DO  
     624               CALL lbc_lnk( 'zgr_bat', bathy, 'T', 1._wp ) 
    612625               WHERE (gphit(:,:) >0._wp) bathy(:,:) = 0._wp 
    613626               ! Dig inlet: 
    614627               WHERE ((gphit(:,:)>0._wp).AND.(glamt(:,:)>-50._wp).AND.(glamt(:,:)<50._wp)) bathy(:,:) = 600._wp 
     628               DEALLOCATE(zbatv) 
    615629            ENDIF 
    616630!            CALL lbc_lnk( 'zgr_bat', bathy, 'T', 1._wp ) 
     
    731745      ENDIF 
    732746      ! 
     747#if defined key_agrif 
     748      IF ( .NOT.Agrif_Root() ) CALL agrif_bathymetry_connect 
     749#endif 
     750      ! 
    733751      IF ( .not. ln_sco ) THEN                                !==  set a minimum depth  ==! 
    734752         IF( rn_hmin < 0._wp ) THEN    ;   ik = - INT( rn_hmin )                                      ! from a nb of level 
     
    827845           mbathy(  mi0(jpiglo-nn_hls):mi1(jpiglo-nn_hls),:) = jpkm1 
    828846         ENDIF 
    829       ELSEIF( l_Iperio ) THEN 
     847      ELSEIF( jperio == 1 .OR. jperio == 4 .OR. jperio ==  6 ) THEN 
    830848         IF(lwp) WRITE(numout,*)' east-west cyclic boundary conditions on mbathy: jperio = ', jperio 
    831          mbathy( 1 ,:) = mbathy(jpim1,:) 
    832          mbathy(jpi,:) = mbathy(  2  ,:) 
     849!         mbathy( 1 ,:) = mbathy(jpim1,:) 
     850!         mbathy(jpi,:) = mbathy(  2  ,:) 
    833851      ELSEIF( jperio == 2 ) THEN 
    834852         IF(lwp) WRITE(numout,*) '   equatorial boundary conditions on mbathy: jperio = ', jperio 
     
    14091427      ! Envelope bathymetry saved in hbatt 
    14101428      hbatt(:,:) = zenv(:,:)  
    1411       IF( MINVAL( gphit(:,:) ) * MAXVAL( gphit(:,:) ) <= 0._wp ) THEN 
     1429      IF ((ntopo>0).AND.MINVAL( gphit(:,:) ) * MAXVAL( gphit(:,:) ) <= 0._wp ) THEN 
    14121430         CALL ctl_warn( ' s-coordinates are tapered in vicinity of the Equator' ) 
    14131431         DO jj = 1, jpj 
     
    15321550         END DO 
    15331551      END DO 
     1552 
     1553      WHERE (bathy(:,:)<=0) mbathy(:,:) = 0 
     1554 
    15341555      IF(lwp ) WRITE(numout,*) ' MIN val mbathy h90 ', MINVAL( mbathy(:,:) ),   & 
    15351556         &                                                       ' MAX ', MAXVAL( mbathy(:,:) ) 
Note: See TracChangeset for help on using the changeset viewer.