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

Ignore:
Timestamp:
2020-07-02T10:38:35+02:00 (4 years ago)
Author:
smasson
Message:

tools: update with tools_dev_r12970_AGRIF_CMEMS

File:
1 edited

Legend:

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

    r12870 r13204  
    6262      !!              - 1D configuration, move Coriolis, u and v at T-point 
    6363      !!---------------------------------------------------------------------- 
     64      INTEGER ::   jk          ! dummy loop indices 
     65      INTEGER ::   iconf = 0   ! local integers 
     66      REAL(wp), POINTER, DIMENSION(:,:) ::   z1_hu_0, z1_hv_0 
     67      INTEGER , DIMENSION(jpi,jpj) ::   ik_top , ik_bot       ! top and bottom ocean level 
     68      !!---------------------------------------------------------------------- 
    6469      ! 
    6570      IF(lwp) THEN 
     
    7176      !                       !==  Reference coordinate system  ==! 
    7277      ! 
    73       CALL dom_nam                  ! read namelist ( namrun, namdom ) 
    74       ! 
    75       CALL dom_hgr                  ! Horizontal mesh 
    76       ! 
    77       CALL dom_zgr                  ! Vertical mesh and bathymetry 
    78       ! 
    79       CALL dom_msk                  ! compute mask (needed by write_cfg) 
    80       ! 
    81       IF ( ln_domclo ) CALL dom_clo ! Closed seas and lake 
     78      CALL dom_nam               ! read namelist ( namrun, namdom ) 
     79                  !   CALL dom_clo               ! Closed seas and lake 
     80          
     81      CALL dom_hgr               ! Horizontal mesh 
     82      CALL dom_zgr( ik_top, ik_bot )  ! Vertical mesh and bathymetry 
     83      CALL dom_msk( ik_top, ik_bot )  ! Masks 
     84      ! 
    8285      ! 
    8386      CALL dom_ctl                  ! print extrema of masked scale factors 
    8487      !  
     88#if ! defined key_agrif 
    8589      CALL cfg_write                ! create the configuration file 
     90#endif 
    8691      ! 
    8792   END SUBROUTINE dom_init 
     
    98103      !!---------------------------------------------------------------------- 
    99104      USE ioipsl 
    100       NAMELIST/namrun/ cn_ocerst_indir, cn_ocerst_outdir, nn_stocklist, ln_rst_list,                 & 
    101                        nn_no   , cn_exp   , cn_ocerst_in, cn_ocerst_out, ln_rstart , nn_rstctl ,     & 
    102          &             nn_it000, nn_itend , nn_date0    , nn_time0     , nn_leapy  , nn_istate ,     & 
    103          &             nn_stock, nn_write , ln_mskland  , ln_clobber   , nn_chunksz, nn_euler  ,     & 
     105      NAMELIST/namrun/ cn_exp   ,    &           
     106         &             nn_it000, nn_itend , nn_date0    , nn_time0     , nn_leapy  ,     & 
     107         &             ln_mskland  , ln_clobber   , nn_chunksz,     & 
    104108         &             ln_cfmeta, ln_iscpl 
    105       NAMELIST/namdom/ nn_bathy, cn_topo, cn_bath, cn_lon, cn_lat, nn_interp,                        & 
    106          &             rn_bathy , rn_e3zps_min, rn_e3zps_rat, nn_msh, rn_hmin,                       & 
    107          &             rn_atfp , rn_rdt   , ln_crs      , jphgr_msh ,                                & 
     109 
     110      NAMELIST/namdom/ ln_read_cfg, nn_bathy, cn_domcfg, cn_topo, cn_bath, cn_lon, cn_lat, rn_scale, nn_interp, & 
     111         &              rn_bathy , rn_e3zps_min, rn_e3zps_rat, nn_msh, rn_hmin,            & 
     112         &             rn_atfp , rn_rdt   ,  ln_crs      , jphgr_msh ,                               & 
    108113         &             ppglam0, ppgphi0, ppe1_deg, ppe2_deg, ppe1_m, ppe2_m,                         & 
    109114         &             ppsur, ppa0, ppa1, ppkth, ppacr, ppdzmin, pphmax, ldbletanh,                  & 
    110115         &             ppa2, ppkth2, ppacr2 
    111  
    112  
    113116 
    114117      INTEGER  ::   ios                 ! Local integer output status for namelist read 
     
    137140 
    138141      cexper = cn_exp 
    139       nrstdt = nn_rstctl 
    140142      nit000 = nn_it000 
    141143      nitend = nn_itend 
    142144      ndate0 = nn_date0 
    143145      nleapy = nn_leapy 
    144       ninist = nn_istate 
    145       nstock = nn_stock 
    146       nstocklist = nn_stocklist 
    147       nwrite = nn_write 
    148       neuler = nn_euler 
    149       IF ( neuler == 1 .AND. .NOT. ln_rstart ) THEN 
    150          WRITE(ctmp1,*) 'ln_rstart =.FALSE., nn_euler is forced to 0 ' 
    151          CALL ctl_warn( ctmp1 ) 
    152          neuler = 0 
    153       ENDIF 
    154  
    155       !                             ! control of output frequency 
    156       IF ( nstock == 0 .OR. nstock > nitend ) THEN 
    157          WRITE(ctmp1,*) 'nstock = ', nstock, ' it is forced to ', nitend 
    158          CALL ctl_warn( ctmp1 ) 
    159          nstock = nitend 
    160       ENDIF 
    161       IF ( nwrite == 0 ) THEN 
    162          WRITE(ctmp1,*) 'nwrite = ', nwrite, ' it is forced to ', nitend 
    163          CALL ctl_warn( ctmp1 ) 
    164          nwrite = nitend 
    165       ENDIF 
    166  
    167  
    168  
    169  
    170       SELECT CASE ( nleapy )        ! Choose calendar for IOIPSL 
    171       CASE (  1 )  
    172          CALL ioconf_calendar('gregorian') 
    173          IF(lwp) WRITE(numout,*) '   The IOIPSL calendar is "gregorian", i.e. leap year' 
    174       CASE (  0 ) 
    175          CALL ioconf_calendar('noleap') 
    176          IF(lwp) WRITE(numout,*) '   The IOIPSL calendar is "noleap", i.e. no leap year' 
    177       CASE ( 30 ) 
    178          CALL ioconf_calendar('360d') 
    179          IF(lwp) WRITE(numout,*) '   The IOIPSL calendar is "360d", i.e. 360 days in a year' 
    180       END SELECT 
    181  
    182  
    183  
     146 
     147      !  
     148      cn_topo ='' 
     149      cn_bath ='' 
     150      cn_lon  ='' 
     151      cn_lat  ='' 
     152      rn_scale = 1. 
    184153 
    185154      REWIND( numnam_ref )              ! Namelist namdom in reference namelist : space & time domain (bathymetry, mesh, timestep) 
     
    193162      IF(lwm) WRITE ( numond, namdom ) 
    194163      ! 
     164 
     165 
     166 
    195167      IF(lwp) THEN 
    196168         WRITE(numout,*) 
     
    198170         WRITE(numout,*) '      flag read/compute bathymetry      nn_bathy     = ', nn_bathy 
    199171         IF( nn_bathy == 2 ) THEN 
    200             WRITE(numout,*) '      compute bathymetry from file      cn_topo      = ', cn_topo 
     172            WRITE(numout,*) '   compute bathymetry from file      cn_topo      = ' , cn_topo 
     173            WRITE(numout,*) '   bathymetry name in file           cn_bath      = ' , cn_bath 
     174            WRITE(numout,*) '   longitude name in file            cn_lon       = ' , cn_lon 
     175            WRITE(numout,*) '   latitude  name in file            cn_lat       = ' , cn_lat 
     176            WRITE(numout,*) '   bathmetry scale factor            rn_scale     = ' , rn_scale  
    201177         ENDIF    
    202178         WRITE(numout,*) '      Depth (if =0 bathy=jpkm1)         rn_bathy     = ', rn_bathy 
     
    255231      !!---------------------------------------------------------------------- 
    256232      ! 
     233#undef CHECK_DOM 
     234#ifdef CHECK_DOM 
    257235      IF(lk_mpp) THEN 
    258236         CALL mpp_minloc( 'dom_ctl', e1t(:,:), tmask_i(:,:), ze1min, iloc ) 
     
    292270         WRITE(numout,"(14x,'e2t mini: ',1f10.2,' at i = ',i5,' j= ',i5)") ze2min, iimi2, ijmi2 
    293271      ENDIF 
     272#endif 
    294273      ! 
    295274      ! check that all processes are still there... If some process have an error, 
     
    426405      CALL iom_rstput( 0, 0, inum, 'top_level'    , REAL( mikt, wp )*ssmask , ktype = jp_i4 )   ! nb of ocean T-points (ISF) 
    427406      CALL iom_rstput( 0, 0, inum, 'isf_draft'    , risfdep , ktype = jp_r8 ) 
    428       CALL iom_rstput( 0, 0, inum, 'bathy_metry'  , bathy   , ktype = jp_r8 ) 
     407      DO jj = 1,jpj 
     408         DO ji = 1,jpi 
     409            z2d (ji,jj) = SUM ( e3t_0(ji,jj, 1:mbkt(ji,jj) ) ) * ssmask(ji,jj)  
     410         END DO 
     411      END DO 
     412      CALL iom_rstput( 0, 0, inum, 'bathy_metry'   , z2d , ktype = jp_r8 ) 
    429413      ! 
    430414      !                              !== closed sea ==! 
Note: See TracChangeset for help on using the changeset viewer.