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 11201 for NEMO/branches/2019/ENHANCE-03_domcfg – NEMO

Ignore:
Timestamp:
2019-07-01T12:10:15+02:00 (5 years ago)
Author:
mathiot
Message:

ENHANCE-03_domcfg : add management of closed seas in domain cfg by flood filling and lat/lon seed instead of i/j box definition (ticket #2143)

Location:
NEMO/branches/2019/ENHANCE-03_domcfg
Files:
2 added
11 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/ENHANCE-03_domcfg/namelist_ref

    r11133 r11201  
    4242   nn_bathy    =    1      !  compute (=0) or read (=1) the bathymetry file 
    4343   rn_bathy    =    0.     !  value of the bathymetry. if (=0) bottom flat at jpkm1 
    44    nn_closea   =    0      !  remove (=0) or keep (=1) closed seas and lakes (ORCA) 
    45    nn_msh      =    1      !  create (=1) a mesh file or not (=0) 
     44   nn_msh      =    0      !  create (=1) a mesh file or not (=0) 
    4645   rn_hmin     =   -3.     !  min depth of the ocean (>0) or min number of ocean level (<0) 
    4746   rn_isfhmin  =    1.00   !  treshold (m) to discriminate grounding ice to floating ice 
     
    9392   jpiglo      =     10    !  1st dimension of global domain --> i =jpidta 
    9493   jpjglo      =     12    !  2nd    -                  -    --> j =jpjdta 
    95    jpizoom     =      1    !  left bottom (i,j) indices of the zoom 
    96    jpjzoom     =      1    !  in data domain indices 
    9794   jperio      =      0    !  lateral cond. type (between 0 and 6) 
    9895                                 !  = 0 closed                 ;   = 1 cyclic East-West 
     
    103100   ln_use_jattr = .false.  !  use (T) the file attribute: open_ocean_jstart, if present 
    104101                           !  in netcdf input files, as the start j-row for reading 
     102   ln_domclo = .true.      ! computation of closed sea masks (see namclo) 
    105103/ 
    106104!----------------------------------------------------------------------- 
     
    137135                        !!!!!!!! Other stretching (not SH94 or SF12) [also uses rn_theta above] 
    138136   rn_thetb    =    1.0    !  bottom control parameter  (0<=thetb<= 1) 
     137/ 
     138!----------------------------------------------------------------------- 
     139&namclo ! (closed sea : need ln_domclo = .true. in namcfg) 
     140!----------------------------------------------------------------------- 
     141   rn_lon_opnsea = -2.0     ! longitude seed of open ocean 
     142   rn_lat_opnsea = -2.0     ! latitude  seed of open ocean 
     143   nn_closea = 8           ! number of closed seas ( = 0; only the open_sea mask will be computed) 
     144   !                name   ! lon_src ! lat_src ! lon_trg ! lat_trg ! river mouth area   ! net evap/precip correction scheme ! radius tgt   ! id trg 
     145   !                       ! (degree)! (degree)! (degree)! (degree)! local/coast/global ! (glo/rnf/emp)                     !     (m)      ! 
     146   ! North American lakes 
     147   sn_lake(1) = 'superior' ,  -86.57 ,  47.30  , -66.49  , 50.45   , 'local'            , 'rnf'                             ,   550000.0 , 2     
     148   sn_lake(2) = 'michigan' ,  -87.06 ,  42.74  , -66.49  , 50.45   , 'local'            , 'rnf'                             ,   550000.0 , 2     
     149   sn_lake(3) = 'huron'    ,  -82.51 ,  44.74  , -66.49  , 50.45   , 'local'            , 'rnf'                             ,   550000.0 , 2     
     150   sn_lake(4) = 'erie'     ,  -81.13 ,  42.25  , -66.49  , 50.45   , 'local'            , 'rnf'                             ,   550000.0 , 2     
     151   sn_lake(5) = 'ontario'  ,  -77.72 ,  43.62  , -66.49  , 50.45   , 'local'            , 'rnf'                             ,   550000.0 , 2     
     152   ! African Lake 
     153   sn_lake(6) = 'victoria' ,   32.93 ,  -1.08  ,  30.44  , 31.37   , 'coast'            , 'emp'                             ,   100000.0 , 3     
     154   ! Asian Lakes 
     155   sn_lake(7) = 'caspian'  ,   50.0  ,  44.0   ,   0.0   ,  0.0    , 'global'           , 'glo'                             ,        0.0 , 1      
     156   sn_lake(8) = 'aral'     ,   60.0  ,  45.0   ,   0.0   ,  0.0    , 'global'           , 'glo'                             ,        0.0 , 1     
    139157/ 
    140158!----------------------------------------------------------------------- 
  • NEMO/branches/2019/ENHANCE-03_domcfg/src/dom_oce.F90

    r11129 r11201  
    3636   REAL(wp), PUBLIC ::   rn_e3zps_rat    !: minimum thickness ration for partial steps 
    3737   INTEGER , PUBLIC ::   nn_msh          !: = 1 create a mesh-mask file 
    38    INTEGER , PUBLIC ::   nn_closea       !: =0 suppress closed sea/lake from the ORCA domain or not (=1) 
    3938 
    4039   INTEGER, PUBLIC :: nn_interp 
     
    5049   LOGICAL, PUBLIC ::   lzoom_n    =  .FALSE.   !: North zoom type flag 
    5150 
    52    LOGICAL, PUBLIC ::   ln_closea  =  .FALSE. 
     51   LOGICAL, PUBLIC ::   ln_domclo  =  .FALSE. 
    5352 
    5453   INTEGER       ::   jphgr_msh          !: type of horizontal mesh 
     
    210209   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   gdepw_0 !: w- depth              [m] 
    211210   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   gde3w_0 !: w- depth (sum of e3w) [m] 
    212    !  
    213    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ht_0  !: t-depth              [m] 
    214    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hu_0  !: u-depth              [m] 
    215    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hv_0  !: v-depth              [m] 
    216  
     211   ! 
    217212   INTEGER, PUBLIC ::   nla10              !: deepest    W level Above  ~10m (nlb10 - 1) 
    218213   INTEGER, PUBLIC ::   nlb10              !: shallowest W level Bellow ~10m (nla10 + 1)  
    219  
     214   ! 
    220215   !! 1D reference  vertical coordinate 
    221216   !! =-----------------====------ 
     
    243238   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ssmask, ssumask, ssvmask             !: surface mask at T-,U-, V- and F-pts 
    244239   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:), TARGET :: tmask, umask, vmask, fmask   !: land/ocean mask at T-, U-, V- and F-pts 
    245    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:), TARGET :: wmask, wumask, wvmask        !: land/ocean mask at WT-, WU- and WV-pts 
     240   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:), TARGET :: wmask                        !: land/ocean mask at W- pts                
     241 
     242   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: msk_opnsea, msk_closea                 !: open ocean mask, closed sea mask (all of them) 
     243   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: msk_glo  , msk_rnf  , msk_emp                !: closed sea masks 
     244   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: msk_gloid, msk_rnfid, msk_empid              !: closed sea masks 
    246245 
    247246   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   tpol, fpol          !: north fold mask (jperio= 3 or 4) 
     
    302301   INTEGER FUNCTION dom_oce_alloc() 
    303302      !!---------------------------------------------------------------------- 
    304       INTEGER, DIMENSION(12) :: ierr 
     303      INTEGER, DIMENSION(11) :: ierr 
    305304      !!---------------------------------------------------------------------- 
    306305      ierr(:) = 0 
     
    328327         &      e3uw_0(jpi,jpj,jpk) , e3vw_0(jpi,jpj,jpk) , STAT=ierr(5) )                        
    329328         ! 
    330       ALLOCATE( ht_0(jpi,jpj) , hu_0(jpi,jpj) , hv_0(jpi,jpj) , STAT=ierr(6)  ) 
    331          ! 
    332          ! 
    333       ALLOCATE( gdept_1d(jpk) , e3tp (jpi,jpj), e3wp(jpi,jpj) ,gdepw_1d(jpk) , e3t_1d(jpk) , e3w_1d(jpk) , STAT=ierr(7) ) 
     329      ALLOCATE( gdept_1d(jpk) , e3tp (jpi,jpj), e3wp(jpi,jpj) ,gdepw_1d(jpk) , e3t_1d(jpk) , e3w_1d(jpk) , STAT=ierr(6) ) 
    334330         ! 
    335331      ALLOCATE( bathy(jpi,jpj),mbathy(jpi,jpj), tmask_i(jpi,jpj) , tmask_h(jpi,jpj) ,                        &  
    336332         &      ssmask (jpi,jpj) , ssumask(jpi,jpj) , ssvmask(jpi,jpj) ,     & 
    337          &      mbkt   (jpi,jpj) , mbku   (jpi,jpj) , mbkv   (jpi,jpj) , STAT=ierr(9) ) 
     333         &      mbkt   (jpi,jpj) , mbku   (jpi,jpj) , mbkv   (jpi,jpj) , STAT=ierr(7) ) 
    338334         ! 
    339335      ALLOCATE( misfdep(jpi,jpj) , mikt(jpi,jpj) , miku(jpi,jpj) ,     & 
    340          &      risfdep(jpi,jpj) , mikv(jpi,jpj) , mikf(jpi,jpj) , STAT=ierr(10) ) 
     336         &      risfdep(jpi,jpj) , mikv(jpi,jpj) , mikf(jpi,jpj) , STAT=ierr(8) ) 
    341337         ! 
    342338      ALLOCATE( tmask(jpi,jpj,jpk) , umask(jpi,jpj,jpk) ,     &  
    343          &      vmask(jpi,jpj,jpk) , fmask(jpi,jpj,jpk) , STAT=ierr(11) ) 
    344          ! 
    345       ALLOCATE( wmask(jpi,jpj,jpk) , wumask(jpi,jpj,jpk), wvmask(jpi,jpj,jpk) , STAT=ierr(12) ) 
    346  
     339         &      vmask(jpi,jpj,jpk) , fmask(jpi,jpj,jpk) , wmask(jpi,jpj,jpk) , STAT=ierr(9) ) 
     340         ! 
    347341      ALLOCATE( hbatv (jpi,jpj) , hbatf (jpi,jpj) ,     & 
    348342         &      hbatt (jpi,jpj) , hbatu (jpi,jpj) ,     & 
    349343         &      scosrf(jpi,jpj) , scobot(jpi,jpj) ,     & 
    350344         &      hifv  (jpi,jpj) , hiff  (jpi,jpj) ,     & 
    351          &      hift  (jpi,jpj) , hifu  (jpi,jpj) , STAT=ierr(8) ) 
     345         &      hift  (jpi,jpj) , hifu  (jpi,jpj) , STAT=ierr(10) ) 
     346 
     347      ALLOCATE( msk_opnsea(jpi,jpj), msk_closea(jpi,jpj),                   & 
     348         &      msk_glo  (jpi,jpj), msk_rnf  (jpi,jpj), msk_emp  (jpi,jpj), & 
     349         &      msk_gloid(jpi,jpj), msk_rnfid(jpi,jpj), msk_empid(jpi,jpj), STAT=ierr(11) ) 
    352350      ! 
    353351      dom_oce_alloc = MAXVAL(ierr) 
  • NEMO/branches/2019/ENHANCE-03_domcfg/src/domain.F90

    r11129 r11201  
    2323   USE dom_oce         ! domain: ocean 
    2424   USE phycst          ! physical constants 
    25    !  USE closea          ! closed seas 
    2625   USE domhgr          ! domain: set the horizontal mesh 
    2726   USE domzgr          ! domain: set the vertical mesh 
    2827   USE dommsk          ! domain: set the mask system 
    29    USE domwri          ! domain: write the meshmask file 
     28   USE domclo          ! domain: set closed sea mask 
    3029   ! 
    3130   USE in_out_manager  ! I/O manager 
     
    7574      !                       !==  Reference coordinate system  ==! 
    7675      ! 
    77       CALL dom_nam               ! read namelist ( namrun, namdom ) 
    78       ! 
    79       !   CALL dom_clo               ! Closed seas and lake 
     76      CALL dom_nam                  ! read namelist ( namrun, namdom ) 
     77      ! 
     78      CALL dom_hgr                  ! Horizontal mesh 
     79      ! 
     80      CALL dom_zgr                  ! Vertical mesh and bathymetry 
     81      ! 
     82      IF ( ln_domclo .OR. nmsh > 0 ) CALL dom_msk                  ! compute mask (needed by dom_clo 
     83      ! 
     84      IF ( ln_domclo ) CALL dom_clo ! Closed seas and lake 
    8085      !  
    81       CALL dom_hgr               ! Horizontal mesh 
    82       ! 
    83       CALL dom_zgr               ! Vertical mesh and bathymetry 
    84       ! 
    85       CALL dom_msk               ! Masks 
    86       ! 
    87       ht_0(:,:) = e3t_0(:,:,1) * tmask(:,:,1)   ! Reference ocean thickness 
    88       hu_0(:,:) = e3u_0(:,:,1) * umask(:,:,1) 
    89       hv_0(:,:) = e3v_0(:,:,1) * vmask(:,:,1) 
    90       DO jk = 2, jpk 
    91          ht_0(:,:) = ht_0(:,:) + e3t_0(:,:,jk) * tmask(:,:,jk) 
    92          hu_0(:,:) = hu_0(:,:) + e3u_0(:,:,jk) * umask(:,:,jk) 
    93          hv_0(:,:) = hv_0(:,:) + e3v_0(:,:,jk) * vmask(:,:,jk) 
    94       END DO 
    95       ! 
    96       CALL cfg_write             ! create the configuration file 
    97       ! 
    98       CALL dom_wri 
     86      CALL cfg_write                ! create the configuration file 
    9987      ! 
    10088   END SUBROUTINE dom_init 
     
    118106      NAMELIST/namdom/ nn_bathy, cn_topo, cn_bath, cn_lon, cn_lat, nn_interp,                        & 
    119107         &             rn_bathy , rn_e3zps_min, rn_e3zps_rat, nn_msh, rn_hmin, rn_isfhmin,           & 
    120          &             rn_atfp , rn_rdt   , nn_closea   , ln_crs      , jphgr_msh ,                  & 
     108         &             rn_atfp , rn_rdt   , ln_crs      , jphgr_msh ,                  & 
    121109         &             ppglam0, ppgphi0, ppe1_deg, ppe2_deg, ppe1_m, ppe2_m,                         & 
    122110         &             ppsur, ppa0, ppa1, ppkth, ppacr, ppdzmin, pphmax, ldbletanh,                  & 
     
    142130         WRITE(numout,*) '~~~~~~~ ' 
    143131         WRITE(numout,*) '   Namelist namrun' 
    144          WRITE(numout,*) '      job number                      nn_no      = ', nn_no 
    145132         WRITE(numout,*) '      experiment name for output      cn_exp     = ', cn_exp 
    146          WRITE(numout,*) '      file prefix restart input       cn_ocerst_in= ', cn_ocerst_in 
    147          WRITE(numout,*) '      restart input directory         cn_ocerst_indir= ', cn_ocerst_indir 
    148          WRITE(numout,*) '      file prefix restart output      cn_ocerst_out= ', cn_ocerst_out 
    149          WRITE(numout,*) '      restart output directory        cn_ocerst_outdir= ', cn_ocerst_outdir 
    150          WRITE(numout,*) '      restart logical                 ln_rstart  = ', ln_rstart 
    151          WRITE(numout,*) '      start with forward time step    nn_euler   = ', nn_euler 
    152          WRITE(numout,*) '      control of time step            nn_rstctl  = ', nn_rstctl 
    153          WRITE(numout,*) '      number of the first time step   nn_it000   = ', nn_it000 
    154          WRITE(numout,*) '      number of the last time step    nn_itend   = ', nn_itend 
    155          WRITE(numout,*) '      initial calendar date aammjj    nn_date0   = ', nn_date0 
    156          WRITE(numout,*) '      initial time of day in hhmm     nn_time0   = ', nn_time0 
    157          WRITE(numout,*) '      leap year calendar (0/1)        nn_leapy   = ', nn_leapy 
    158          WRITE(numout,*) '      initial state output            nn_istate  = ', nn_istate 
    159          IF( ln_rst_list ) THEN 
    160             WRITE(numout,*) '      list of restart dump times      nn_stocklist   =', nn_stocklist 
    161          ELSE 
    162             WRITE(numout,*) '      frequency of restart file       nn_stock   = ', nn_stock 
    163          ENDIF 
    164          WRITE(numout,*) '      frequency of output file        nn_write   = ', nn_write 
    165133         WRITE(numout,*) '      mask land points                ln_mskland = ', ln_mskland 
    166134         WRITE(numout,*) '      additional CF standard metadata ln_cfmeta  = ', ln_cfmeta 
    167135         WRITE(numout,*) '      overwrite an existing file      ln_clobber = ', ln_clobber 
    168136         WRITE(numout,*) '      NetCDF chunksize (bytes)        nn_chunksz = ', nn_chunksz 
    169          WRITE(numout,*) '      IS coupling at the restart step ln_iscpl   = ', ln_iscpl 
    170137      ENDIF 
    171138 
     
    245212         WRITE(numout,*) '           = 2   mesh and mask             ' 
    246213         WRITE(numout,*) '           = 3   mesh_hgr, msh_zgr and mask' 
    247          WRITE(numout,*) '      ocean time step                       rn_rdt    = ', rn_rdt 
    248          WRITE(numout,*) '      asselin time filter parameter         rn_atfp   = ', rn_atfp 
    249          WRITE(numout,*) '      suppression of closed seas (=0)       nn_closea = ', nn_closea 
    250          WRITE(numout,*) '      online coarsening of dynamical fields ln_crs    = ', ln_crs 
    251214         WRITE(numout,*) '      type of horizontal mesh jphgr_msh           = ', jphgr_msh 
    252215         WRITE(numout,*) '      longitude of first raw and column T-point ppglam0 = ', ppglam0 
     
    453416      END DO 
    454417      CALL iom_rstput( 0, 0, inum, 'bathy_metry'   , z2d , ktype = jp_r4 ) 
    455  
    456       ! 
    457       IF( ln_sco ) THEN             ! s-coordinate: store grid stiffness ratio  (Not required anyway) 
    458          CALL dom_stiff( z2d ) 
    459          CALL iom_rstput( 0, 0, inum, 'stiffness', z2d )        !    ! Max. grid stiffness ratio 
    460       ENDIF 
     418      ! 
     419      !                              !== closed sea ==! 
     420      IF (ln_domclo) THEN 
     421         ! mask for the open sea 
     422         CALL iom_rstput( 0, 0, inum, 'mask_opensea', msk_opnsea, ktype = jp_i4 ) 
     423         ! mask for all the under closed sea 
     424         CALL iom_rstput( 0, 0, inum, 'mask_csundef', msk_closea, ktype = jp_i4 ) 
     425         ! mask for global, local net precip, local net precip and evaporation correction 
     426         CALL iom_rstput( 0, 0, inum, 'mask_csglo', msk_glo, ktype = jp_i4 ) 
     427         CALL iom_rstput( 0, 0, inum, 'mask_csemp', msk_emp, ktype = jp_i4 ) 
     428         CALL iom_rstput( 0, 0, inum, 'mask_csrnf', msk_rnf, ktype = jp_i4 ) 
     429         ! mask for the various river mouth (in case multiple lake in the same outlet) 
     430         CALL iom_rstput( 0, 0, inum, 'mask_csgrpglo', msk_gloid, ktype = jp_i4 ) 
     431         CALL iom_rstput( 0, 0, inum, 'mask_csgrpemp', msk_empid, ktype = jp_i4 ) 
     432         CALL iom_rstput( 0, 0, inum, 'mask_csgrprnf', msk_rnfid, ktype = jp_i4 ) 
     433      END IF 
    461434      ! 
    462435      !                                ! ============================ 
  • NEMO/branches/2019/ENHANCE-03_domcfg/src/dombat.F90

    r11129 r11201  
    88   USE lbclnk            ! ocean lateral boundary conditions (or mpp link) 
    99   USE lib_mpp           ! distributed memory computing library 
    10    USE wrk_nemo          ! Memory allocation 
    1110   USE agrif_modutil 
    1211   USE bilinear_interp 
  • NEMO/branches/2019/ENHANCE-03_domcfg/src/domhgr.F90

    r11129 r11201  
    2828   USE in_out_manager ! I/O manager 
    2929   USE lib_mpp        ! MPP library 
    30    USE timing         ! Timing 
    3130 
    3231   IMPLICIT NONE 
  • NEMO/branches/2019/ENHANCE-03_domcfg/src/dommsk.F90

    r11129 r11201  
    2424   !!---------------------------------------------------------------------- 
    2525   USE dom_oce        ! ocean space and time domain 
     26   USE domwri         ! domain: write the meshmask file 
    2627   USE bdy_oce        ! open boundary 
    2728   ! 
     
    6061      !!      and ko_bot, the indices of the fist and last ocean t-levels which  
    6162      !!      are either defined in usrdef_zgr or read in zgr_read. 
    62       !!                The velocity masks (umask, vmask, wmask, wumask, wvmask)  
     63      !!                The velocity masks (umask, vmask)  
    6364      !!      are deduced from a product of the two neighboring tmask. 
    6465      !!                The vorticity mask (fmask) is deduced from tmask taking 
     
    7576      !!                due to cyclic or North Fold boundaries as well as MPP halos. 
    7677      !! 
    77       !! ** Action :   tmask, umask, vmask, wmask, wumask, wvmask : land/ocean mask  
     78      !! ** Action :   tmask, umask, vmask, wmask : land/ocean mask  
    7879      !!                         at t-, u-, v- w, wu-, and wv-points (=0. or 1.) 
    7980      !!               fmask   : land/ocean mask at f-point (=0., or =1., or  
     
    188189      !----------------------------------------- 
    189190      wmask (:,:,1) = tmask(:,:,1)     ! surface 
    190       wumask(:,:,1) = umask(:,:,1) 
    191       wvmask(:,:,1) = vmask(:,:,1) 
    192191      DO jk = 2, jpk                   ! interior values 
    193192         wmask (:,:,jk) = tmask(:,:,jk) * tmask(:,:,jk-1) 
    194          wumask(:,:,jk) = umask(:,:,jk) * umask(:,:,jk-1)    
    195          wvmask(:,:,jk) = vmask(:,:,jk) * vmask(:,:,jk-1) 
    196193      END DO 
    197194 
     
    202199      ssumask(:,:) = MAXVAL( umask(:,:,:), DIM=3 ) 
    203200      ssvmask(:,:) = MAXVAL( vmask(:,:,:), DIM=3 ) 
    204  
    205201 
    206202      ! Interior domain mask  (used for global sum) 
     
    289285      ENDIF 
    290286      ! 
     287      ! write out mesh mask 
     288      IF ( nn_msh > 0 ) CALL dom_wri 
     289      ! 
    291290   END SUBROUTINE dom_msk 
    292291    
  • NEMO/branches/2019/ENHANCE-03_domcfg/src/domngb.F90

    r10727 r11201  
    1111   !!---------------------------------------------------------------------- 
    1212   USE dom_oce        ! ocean space and time domain 
     13   USE phycst 
    1314   ! 
    1415   USE in_out_manager ! I/O manager 
     
    1819   PRIVATE 
    1920 
    20    PUBLIC   dom_ngb   ! routine called in iom.F90 module 
     21   PUBLIC   dom_ngb   ! routine called in iom.F90 and domclo.F90 module 
     22   PUBLIC   dist 
    2123 
    2224   !!---------------------------------------------------------------------- 
     
    2729CONTAINS 
    2830 
    29    SUBROUTINE dom_ngb( plon, plat, kii, kjj, cdgrid, kkk ) 
     31   SUBROUTINE dom_ngb( plon, plat, kii, kjj, rdist, cdgrid, kkk ) 
    3032      !!---------------------------------------------------------------------- 
    3133      !!                    ***  ROUTINE dom_ngb  *** 
     
    3739      !!---------------------------------------------------------------------- 
    3840      REAL(wp)        , INTENT(in   ) ::   plon, plat   ! longitude,latitude of the point 
     41      REAL(wp)        , INTENT(  out) ::   rdist        ! distance between the located point and the source 
    3942      INTEGER         , INTENT(  out) ::   kii, kjj     ! i-,j-index of the closes grid point 
    4043      INTEGER         , INTENT(in   ), OPTIONAL :: kkk  ! k-index of the mask level used 
     
    4346      INTEGER :: ik         ! working level 
    4447      INTEGER , DIMENSION(2) ::   iloc 
    45       REAL(wp)               ::   zlon, zmini 
    4648      REAL(wp), DIMENSION(jpi,jpj) ::   zglam, zgphi, zmask, zdist 
    4749      !!-------------------------------------------------------------------- 
     
    5759      END SELECT 
    5860 
    59       zlon       = MOD( plon       + 720., 360. )                                     ! plon between    0 and 360 
    60       zglam(:,:) = MOD( zglam(:,:) + 720., 360. )                                     ! glam between    0 and 360 
    61       IF( zlon > 270. )   zlon = zlon - 360.                                          ! zlon between  -90 and 270 
    62       IF( zlon <  90. )   WHERE( zglam(:,:) > 180. ) zglam(:,:) = zglam(:,:) - 360.   ! glam between -180 and 180 
    63       zglam(:,:) = zglam(:,:) - zlon 
    64  
    65       zgphi(:,:) = zgphi(:,:) - plat 
    66       zdist(:,:) = zglam(:,:) * zglam(:,:) + zgphi(:,:) * zgphi(:,:) 
     61      zdist = dist(plon, plat, zglam, zgphi) 
    6762       
    6863      IF( lk_mpp ) THEN   
    69          CALL mpp_minloc( 'domngb', zdist(:,:), zmask, zmini, iloc) 
     64         CALL mpp_minloc( 'domngb', zdist(:,:), zmask, rdist, iloc) 
    7065         kii = iloc(1) ; kjj = iloc(2) 
    7166      ELSE 
    7267         iloc(:) = MINLOC( zdist(:,:), mask = zmask(:,:) == 1.e0 ) 
     68         rdist = MINVAL( zdist(:,:) ) 
    7369         kii = iloc(1) + nimpp - 1 
    7470         kjj = iloc(2) + njmpp - 1 
     
    7773   END SUBROUTINE dom_ngb 
    7874 
     75   FUNCTION dist(plonsrc, platsrc, plontrg, plattrg) 
     76      REAL(wp), INTENT(in) :: plonsrc, platsrc                     ! lat/lon of the source point 
     77      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: plontrg, plattrg ! lat/lon of the target (2d in this case) 
     78 
     79      REAL(wp) :: zxs, zys, zzs 
     80      REAL(wp), DIMENSION(jpi,jpj) :: zxt, zyt, zzt 
     81 
     82      REAL(wp), DIMENSION(jpi,jpj) :: dist ! distance between src and trg 
     83 
     84      zxs = COS( rad * platsrc ) * COS( rad * plonsrc ) 
     85      zys = COS( rad * platsrc ) * SIN( rad * plonsrc ) 
     86      zzs = SIN( rad * platsrc ) 
     87 
     88      zxt = COS( rad * plattrg ) * COS( rad * plontrg ) 
     89      zyt = COS( rad * plattrg ) * SIN( rad * plontrg ) 
     90      zzt = SIN( rad * plattrg ) 
     91 
     92      dist(:,:) = ( zxs - zxt(:,:) )**2   & 
     93         &      + ( zys - zyt(:,:) )**2   & 
     94         &      + ( zzs - zzt(:,:) )**2 
     95 
     96      dist = ra * SQRT( dist ) 
     97 
     98   END FUNCTION dist 
     99 
    79100   !!====================================================================== 
    80101END MODULE domngb 
  • NEMO/branches/2019/ENHANCE-03_domcfg/src/domwri.F90

    r10727 r11201  
    177177      ENDIF 
    178178      ! 
    179    !   IF( ll_wd ) CALL iom_rstput( 0, 0, inum, 'ht_0'   , ht_0   , ktype = jp_r8 ) 
    180  
    181179      !                                     ! ============================ 
    182180      CALL iom_close( inum )                !        close the files  
  • NEMO/branches/2019/ENHANCE-03_domcfg/src/domzgr.F90

    r11129 r11201  
    3636   !!--------------------------------------------------------------------- 
    3737   USE dom_oce           ! ocean domain 
    38 !   USE closea            ! closed seas 
    3938   ! 
    4039   USE in_out_manager    ! I/O manager 
     
    164163      ! final adjustment of mbathy & check  
    165164      ! ----------------------------------- 
    166       IF( lzoom       )   CALL zgr_bat_zoom     ! correct mbathy in case of zoom subdomain 
    167165                          CALL zgr_bat_ctl      ! check bathymetry (mbathy) and suppress isolated ocean points 
    168166                          CALL zgr_bot_level    ! deepest ocean level for t-, u- and v-points 
     
    622620      ENDIF 
    623621      ! 
    624     !  IF( nn_closea == 0 )   CALL clo_bat( bathy, mbathy )    !==  NO closed seas or lakes  ==! 
    625       !                        
    626622      IF ( .not. ln_sco ) THEN                                !==  set a minimum depth  ==! 
    627623         IF( rn_hmin < 0._wp ) THEN    ;   ik = - INT( rn_hmin )                                      ! from a nb of level 
     
    636632      ! 
    637633   END SUBROUTINE zgr_bat 
    638  
    639  
    640    SUBROUTINE zgr_bat_zoom 
    641       !!---------------------------------------------------------------------- 
    642       !!                    ***  ROUTINE zgr_bat_zoom  *** 
    643       !! 
    644       !! ** Purpose : - Close zoom domain boundary if necessary 
    645       !!              - Suppress Med Sea from ORCA R2 and R05 arctic zoom 
    646       !! 
    647       !! ** Method  :  
    648       !! 
    649       !! ** Action  : - update mbathy: level bathymetry (in level index) 
    650       !!---------------------------------------------------------------------- 
    651       INTEGER ::   ii0, ii1, ij0, ij1   ! temporary integers 
    652       !!---------------------------------------------------------------------- 
    653       ! 
    654       IF(lwp) WRITE(numout,*) 
    655       IF(lwp) WRITE(numout,*) '    zgr_bat_zoom : modify the level bathymetry for zoom domain' 
    656       IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~~' 
    657       ! 
    658       ! Zoom domain 
    659       ! =========== 
    660       ! 
    661       ! Forced closed boundary if required 
    662       IF( lzoom_s )   mbathy(  : , mj0(jpjzoom):mj1(jpjzoom) )      = 0 
    663       IF( lzoom_w )   mbathy(      mi0(jpizoom):mi1(jpizoom) , :  ) = 0 
    664       IF( lzoom_e )   mbathy(      mi0(jpiglo+jpizoom-1):mi1(jpiglo+jpizoom-1) , :  ) = 0 
    665       IF( lzoom_n )   mbathy(  : , mj0(jpjglo+jpjzoom-1):mj1(jpjglo+jpjzoom-1) )      = 0 
    666       ! 
    667       ! Configuration specific domain modifications 
    668       ! (here, ORCA arctic configuration: suppress Med Sea) 
    669       IF( cp_cfg == "orca" .AND. cp_cfz == "arctic" ) THEN 
    670          SELECT CASE ( jp_cfg ) 
    671          !                                        ! ======================= 
    672          CASE ( 2 )                               !  ORCA_R2 configuration 
    673             !                                     ! ======================= 
    674             IF(lwp) WRITE(numout,*) '                   ORCA R2 arctic zoom: suppress the Med Sea' 
    675             ii0 = 141   ;   ii1 = 162      ! Sea box i,j indices 
    676             ij0 =  98   ;   ij1 = 110 
    677             !                                     ! ======================= 
    678          CASE ( 05 )                              !  ORCA_R05 configuration 
    679             !                                     ! ======================= 
    680             IF(lwp) WRITE(numout,*) '                   ORCA R05 arctic zoom: suppress the Med Sea' 
    681             ii0 = 563   ;   ii1 = 642      ! zero over the Med Sea boxe 
    682             ij0 = 314   ;   ij1 = 370  
    683          END SELECT 
    684          ! 
    685          mbathy( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0   ! zero over the Med Sea boxe 
    686          ! 
    687       ENDIF 
    688       ! 
    689    END SUBROUTINE zgr_bat_zoom 
    690  
    691634 
    692635   SUBROUTINE zgr_bat_ctl 
  • NEMO/branches/2019/ENHANCE-03_domcfg/src/nemogcm.F90

    r11133 r11201  
    149149      NAMELIST/namcfg/ ln_e3_dep,                                & 
    150150         &             cp_cfg, cp_cfz, jp_cfg, jpidta, jpjdta, jpkdta, jpiglo, jpjglo, & 
    151          &             jpizoom, jpjzoom, jperio, ln_use_jattr 
     151         &             jperio, ln_use_jattr, ln_domclo 
    152152      !!---------------------------------------------------------------------- 
    153153      ! 
     
    315315      jsplt     = nn_jsplt 
    316316 
    317      !  IF( .NOT.ln_read_cfg )   ln_closea = .false.   ! dealing possible only with a domcfg file 
    318317      ! 
    319318      !                             ! Parameter control 
  • NEMO/branches/2019/ENHANCE-03_domcfg/src/par_oce.f90

    r10727 r11201  
    1313   PUBLIC 
    1414 
    15    ! zoom starting position 
    16    INTEGER       ::   jpizoom          !: left bottom (i,j) indices of the zoom 
    17    INTEGER       ::   jpjzoom          !: in data domain indices 
    18  
    19   CHARACTER(lc) ::   cp_cfg           !: name of the configuration 
     15   CHARACTER(lc) ::   cp_cfg           !: name of the configuration 
    2016   CHARACTER(lc) ::   cp_cfz           !: name of the zoom of configuration 
    2117   INTEGER       ::   jp_cfg           !: resolution of the configuration 
Note: See TracChangeset for help on using the changeset viewer.