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

Ignore:
Timestamp:
2019-12-06T18:45:39+01:00 (4 years ago)
Author:
mathiot
Message:

merge ENHANCE-03_domcfg and ENHANCE-02_ISF_nemo

File:
1 copied

Legend:

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

    r12100 r12101  
    2121   !!   dom_ctl        : control print for the ocean domain 
    2222   !!---------------------------------------------------------------------- 
    23    USE oce             ! ocean variables 
    2423   USE dom_oce         ! domain: ocean 
    2524   USE phycst          ! physical constants 
    26  !  USE closea          ! closed seas 
    2725   USE domhgr          ! domain: set the horizontal mesh 
    2826   USE domzgr          ! domain: set the vertical mesh 
    29  !  USE domstp          ! domain: set the time-step 
    3027   USE dommsk          ! domain: set the mask system 
    31    USE domwri          ! domain: write the meshmask file 
    32    USE domvvl          ! variable volume 
     28   USE domclo          ! domain: set closed sea mask 
    3329   ! 
     30   USE lib_mpp         ! 
    3431   USE in_out_manager  ! I/O manager 
    3532   USE iom             !  
    36    USE wrk_nemo        ! Memory Allocation 
    37    USE lib_mpp         ! distributed memory computing library 
    38    USE lbclnk          ! ocean lateral boundary condition (or mpp link) 
    39    USE timing          ! Timing 
    4033 
    4134   IMPLICIT NONE 
     
    6962      !!              - 1D configuration, move Coriolis, u and v at T-point 
    7063      !!---------------------------------------------------------------------- 
    71       INTEGER ::   jk          ! dummy loop indices 
    72       INTEGER ::   iconf = 0   ! local integers 
    73       REAL(wp), POINTER, DIMENSION(:,:) ::   z1_hu_0, z1_hv_0 
    74       !!---------------------------------------------------------------------- 
    75       ! 
    76      ! IF( nn_timing == 1 )   CALL timing_start('dom_init') 
    7764      ! 
    7865      IF(lwp) THEN 
     
    8471      !                       !==  Reference coordinate system  ==! 
    8572      ! 
    86                      CALL dom_nam               ! read namelist ( namrun, namdom ) 
    87                   !   CALL dom_clo               ! Closed seas and lake 
    88           
    89                      CALL dom_hgr               ! Horizontal mesh 
    90                      CALL dom_zgr               ! Vertical mesh and bathymetry 
    91                      CALL dom_msk               ! Masks 
    92       ! 
    93       ht_0(:,:) = e3t_0(:,:,1) * tmask(:,:,1)   ! Reference ocean thickness 
    94       hu_0(:,:) = e3u_0(:,:,1) * umask(:,:,1) 
    95       hv_0(:,:) = e3v_0(:,:,1) * vmask(:,:,1) 
    96       DO jk = 2, jpk 
    97          ht_0(:,:) = ht_0(:,:) + e3t_0(:,:,jk) * tmask(:,:,jk) 
    98          hu_0(:,:) = hu_0(:,:) + e3u_0(:,:,jk) * umask(:,:,jk) 
    99          hv_0(:,:) = hv_0(:,:) + e3v_0(:,:,jk) * vmask(:,:,jk) 
    100       END DO 
    101       ! 
    102       !              !==  time varying part of coordinate system  ==! 
    103       ! 
    104       IF( ln_linssh ) THEN          ! Fix in time : set to the reference one for all 
    105          !       before        !          now          !       after         ! 
    106          ;  gdept_b = gdept_0  ;   gdept_n = gdept_0   !        ---          ! depth of grid-points 
    107          ;  gdepw_b = gdepw_0  ;   gdepw_n = gdepw_0   !        ---          ! 
    108          ;                     ;   gde3w_n = gde3w_0   !        ---          ! 
    109          !                                                                   
    110          ;    e3t_b =   e3t_0  ;     e3t_n =   e3t_0   ;   e3t_a =  e3t_0    ! scale factors 
    111          ;    e3u_b =   e3u_0  ;     e3u_n =   e3u_0   ;   e3u_a =  e3u_0    ! 
    112          ;    e3v_b =   e3v_0  ;     e3v_n =   e3v_0   ;   e3v_a =  e3v_0    ! 
    113          ;                     ;     e3f_n =   e3f_0   !        ---          ! 
    114          ;    e3w_b =   e3w_0  ;     e3w_n =   e3w_0   !        ---          ! 
    115          ;   e3uw_b =  e3uw_0  ;    e3uw_n =  e3uw_0   !        ---          ! 
    116          ;   e3vw_b =  e3vw_0  ;    e3vw_n =  e3vw_0   !        ---          ! 
    117          ! 
    118          CALL wrk_alloc( jpi,jpj,   z1_hu_0, z1_hv_0 ) 
    119          ! 
    120          z1_hu_0(:,:) = ssumask(:,:) / ( hu_0(:,:) + 1._wp - ssumask(:,:) )     ! _i mask due to ISF 
    121          z1_hv_0(:,:) = ssvmask(:,:) / ( hv_0(:,:) + 1._wp - ssvmask(:,:) ) 
    122          ! 
    123          !        before       !          now          !       after         ! 
    124          ;                     ;      ht_n =    ht_0   !                     ! water column thickness 
    125          ;     hu_b =    hu_0  ;      hu_n =    hu_0   ;    hu_a =    hu_0   !  
    126          ;     hv_b =    hv_0  ;      hv_n =    hv_0   ;    hv_a =    hv_0   ! 
    127          ;  r1_hu_b = z1_hu_0  ;   r1_hu_n = z1_hu_0   ; r1_hu_a = z1_hu_0   ! inverse of water column thickness 
    128          ;  r1_hv_b = z1_hv_0  ;   r1_hv_n = z1_hv_0   ; r1_hv_a = z1_hv_0   ! 
    129          ! 
    130          CALL wrk_dealloc( jpi,jpj,   z1_hu_0, z1_hv_0 ) 
    131          ! 
    132       ELSE                         ! time varying : initialize before/now/after variables 
    133          ! 
    134          CALL dom_vvl_init  
    135          ! 
    136       ENDIF 
    137       ! 
    138       CALL cfg_write         ! create the configuration file 
    139       ! 
    140     !  IF( nn_timing == 1 )   CALL timing_stop('dom_init') 
     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 
     82      ! 
     83      CALL dom_ctl                  ! print extrema of masked scale factors 
     84      !  
     85      CALL cfg_write                ! create the configuration file 
    14186      ! 
    14287   END SUBROUTINE dom_init 
    143  
    14488 
    14589   SUBROUTINE dom_nam 
     
    160104         &             ln_cfmeta, ln_iscpl 
    161105      NAMELIST/namdom/ nn_bathy, cn_topo, cn_bath, cn_lon, cn_lat, nn_interp,                        & 
    162          &             rn_bathy , rn_e3zps_min, rn_e3zps_rat, nn_msh, rn_hmin, rn_isfhmin,           & 
    163          &             rn_atfp , rn_rdt   , nn_closea   , ln_crs      , jphgr_msh ,                  & 
     106         &             rn_bathy , rn_e3zps_min, rn_e3zps_rat, nn_msh, rn_hmin,                       & 
     107         &             rn_atfp , rn_rdt   , ln_crs      , jphgr_msh ,                                & 
    164108         &             ppglam0, ppgphi0, ppe1_deg, ppe2_deg, ppe1_m, ppe2_m,                         & 
    165109         &             ppsur, ppa0, ppa1, ppkth, ppacr, ppdzmin, pphmax, ldbletanh,                  & 
     
    185129         WRITE(numout,*) '~~~~~~~ ' 
    186130         WRITE(numout,*) '   Namelist namrun' 
    187          WRITE(numout,*) '      job number                      nn_no      = ', nn_no 
    188131         WRITE(numout,*) '      experiment name for output      cn_exp     = ', cn_exp 
    189          WRITE(numout,*) '      file prefix restart input       cn_ocerst_in= ', cn_ocerst_in 
    190          WRITE(numout,*) '      restart input directory         cn_ocerst_indir= ', cn_ocerst_indir 
    191          WRITE(numout,*) '      file prefix restart output      cn_ocerst_out= ', cn_ocerst_out 
    192          WRITE(numout,*) '      restart output directory        cn_ocerst_outdir= ', cn_ocerst_outdir 
    193          WRITE(numout,*) '      restart logical                 ln_rstart  = ', ln_rstart 
    194          WRITE(numout,*) '      start with forward time step    nn_euler   = ', nn_euler 
    195          WRITE(numout,*) '      control of time step            nn_rstctl  = ', nn_rstctl 
    196          WRITE(numout,*) '      number of the first time step   nn_it000   = ', nn_it000 
    197          WRITE(numout,*) '      number of the last time step    nn_itend   = ', nn_itend 
    198          WRITE(numout,*) '      initial calendar date aammjj    nn_date0   = ', nn_date0 
    199          WRITE(numout,*) '      initial time of day in hhmm     nn_time0   = ', nn_time0 
    200          WRITE(numout,*) '      leap year calendar (0/1)        nn_leapy   = ', nn_leapy 
    201          WRITE(numout,*) '      initial state output            nn_istate  = ', nn_istate 
    202          IF( ln_rst_list ) THEN 
    203             WRITE(numout,*) '      list of restart dump times      nn_stocklist   =', nn_stocklist 
    204          ELSE 
    205             WRITE(numout,*) '      frequency of restart file       nn_stock   = ', nn_stock 
    206          ENDIF 
    207          WRITE(numout,*) '      frequency of output file        nn_write   = ', nn_write 
    208132         WRITE(numout,*) '      mask land points                ln_mskland = ', ln_mskland 
    209133         WRITE(numout,*) '      additional CF standard metadata ln_cfmeta  = ', ln_cfmeta 
    210134         WRITE(numout,*) '      overwrite an existing file      ln_clobber = ', ln_clobber 
    211135         WRITE(numout,*) '      NetCDF chunksize (bytes)        nn_chunksz = ', nn_chunksz 
    212          WRITE(numout,*) '      IS coupling at the restart step ln_iscpl   = ', ln_iscpl 
    213136      ENDIF 
    214137 
     
    280203         WRITE(numout,*) '      min depth of the ocean    (>0) or    rn_hmin   = ', rn_hmin 
    281204         WRITE(numout,*) '      min number of ocean level (<0)       ' 
    282          WRITE(numout,*) '      treshold to open the isf cavity   rn_isfhmin   = ', rn_isfhmin, ' (m)' 
    283205         WRITE(numout,*) '      minimum thickness of partial      rn_e3zps_min = ', rn_e3zps_min, ' (m)' 
    284206         WRITE(numout,*) '         step level                     rn_e3zps_rat = ', rn_e3zps_rat 
     
    288210         WRITE(numout,*) '           = 2   mesh and mask             ' 
    289211         WRITE(numout,*) '           = 3   mesh_hgr, msh_zgr and mask' 
    290          WRITE(numout,*) '      ocean time step                       rn_rdt    = ', rn_rdt 
    291          WRITE(numout,*) '      asselin time filter parameter         rn_atfp   = ', rn_atfp 
    292          WRITE(numout,*) '      suppression of closed seas (=0)       nn_closea = ', nn_closea 
    293          WRITE(numout,*) '      online coarsening of dynamical fields ln_crs    = ', ln_crs 
    294212         WRITE(numout,*) '      type of horizontal mesh jphgr_msh           = ', jphgr_msh 
    295213         WRITE(numout,*) '      longitude of first raw and column T-point ppglam0 = ', ppglam0 
     
    337255      !!---------------------------------------------------------------------- 
    338256      ! 
    339 #undef CHECK_DOM 
    340 #ifdef CHECK_DOM 
    341257      IF(lk_mpp) THEN 
    342          CALL mpp_minloc( e1t(:,:), tmask_i(:,:), ze1min, iimi1,ijmi1 ) 
    343          CALL mpp_minloc( e2t(:,:), tmask_i(:,:), ze2min, iimi2,ijmi2 ) 
    344          CALL mpp_maxloc( e1t(:,:), tmask_i(:,:), ze1max, iima1,ijma1 ) 
    345          CALL mpp_maxloc( e2t(:,:), tmask_i(:,:), ze2max, iima2,ijma2 ) 
     258         CALL mpp_minloc( 'dom_ctl', e1t(:,:), tmask_i(:,:), ze1min, iloc ) 
     259         iimi1 = iloc(1) ; ijmi1 = iloc(2) 
     260         CALL mpp_minloc( 'dom_ctl', e2t(:,:), tmask_i(:,:), ze2min, iloc ) 
     261         iimi2 = iloc(1) ; ijmi2 = iloc(2) 
     262         CALL mpp_maxloc( 'dom_ctl', e1t(:,:), tmask_i(:,:), ze1max, iloc ) 
     263         iima1 = iloc(1) ; ijma1 = iloc(2) 
     264         CALL mpp_maxloc( 'dom_ctl', e2t(:,:), tmask_i(:,:), ze2max, iloc ) 
     265         iima2 = iloc(1) ; ijma2 = iloc(2) 
    346266      ELSE 
    347267         ze1min = MINVAL( e1t(:,:), mask = tmask_i(:,:) == 1._wp )     
     
    372292         WRITE(numout,"(14x,'e2t mini: ',1f10.2,' at i = ',i5,' j= ',i5)") ze2min, iimi2, ijmi2 
    373293      ENDIF 
    374 #endif 
    375294      ! 
    376295   END SUBROUTINE dom_ctl 
     
    490409      CALL iom_rstput( 0, 0, inum, 'bottom_level' , REAL( mbkt, wp )*ssmask , ktype = jp_i4 )   ! nb of ocean T-points 
    491410      CALL iom_rstput( 0, 0, inum, 'top_level'    , REAL( mikt, wp )*ssmask , ktype = jp_i4 )   ! nb of ocean T-points (ISF) 
    492       DO jj = 1,jpj 
    493          DO ji = 1,jpi 
    494             z2d (ji,jj) = SUM ( e3t_0(ji,jj, 1:mbkt(ji,jj) ) ) * ssmask(ji,jj)  
    495          END DO 
    496       END DO 
    497       CALL iom_rstput( 0, 0, inum, 'bathy_metry'   , z2d , ktype = jp_r4 ) 
    498  
    499       ! 
    500       IF( ln_sco ) THEN             ! s-coordinate: store grid stiffness ratio  (Not required anyway) 
    501          CALL dom_stiff( z2d ) 
    502          CALL iom_rstput( 0, 0, inum, 'stiffness', z2d )        !    ! Max. grid stiffness ratio 
    503       ENDIF 
     411      CALL iom_rstput( 0, 0, inum, 'isf_draft'    , risfdep , ktype = jp_r8 ) 
     412      CALL iom_rstput( 0, 0, inum, 'bathy_metry'  , bathy   , ktype = jp_r8 ) 
     413      ! 
     414      !                              !== closed sea ==! 
     415      IF (ln_domclo) THEN 
     416         ! mask for the open sea 
     417         CALL iom_rstput( 0, 0, inum, 'mask_opensea' , msk_opnsea  , ktype = jp_i4 ) 
     418         ! mask for all the under closed sea 
     419         CALL iom_rstput( 0, 0, inum, 'mask_csundef' , msk_csundef , ktype = jp_i4 ) 
     420         ! mask for global, local net precip, local net precip and evaporation correction 
     421         CALL iom_rstput( 0, 0, inum, 'mask_csglo'   , msk_csglo   , ktype = jp_i4 ) 
     422         CALL iom_rstput( 0, 0, inum, 'mask_csemp'   , msk_csemp   , ktype = jp_i4 ) 
     423         CALL iom_rstput( 0, 0, inum, 'mask_csrnf'   , msk_csrnf   , ktype = jp_i4 ) 
     424         ! mask for the various river mouth (in case multiple lake in the same outlet) 
     425         CALL iom_rstput( 0, 0, inum, 'mask_csgrpglo', msk_csgrpglo, ktype = jp_i4 ) 
     426         CALL iom_rstput( 0, 0, inum, 'mask_csgrpemp', msk_csgrpemp, ktype = jp_i4 ) 
     427         CALL iom_rstput( 0, 0, inum, 'mask_csgrprnf', msk_csgrprnf, ktype = jp_i4 ) 
     428      END IF 
    504429      ! 
    505430      !                                ! ============================ 
Note: See TracChangeset for help on using the changeset viewer.