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 9161 for branches/2017/dev_merge_2017/NEMOGCM/NEMO – NEMO

Ignore:
Timestamp:
2017-12-22T11:31:53+01:00 (6 years ago)
Author:
davestorkey
Message:

Reformulation of closea module.
See ticket #2000
https://forge.ipsl.jussieu.fr/nemo/wiki/2017WP/ROBUST-14_Dave_Storkey-Closed_Seas_rewrite

Location:
branches/2017/dev_merge_2017/NEMOGCM/NEMO
Files:
1 deleted
7 edited
1 copied

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/DOM/closea.F90

    r9155 r9161  
    2929   USE lbclnk          ! lateral boundary condition - MPP exchanges 
    3030   USE lib_mpp         ! MPP library 
    31    USE timing 
     31   USE timing          ! Timing 
    3232 
    3333   IMPLICIT NONE 
     
    6565   !!---------------------------------------------------------------------- 
    6666   !! NEMO/OPA 4.0 , NEMO Consortium (2016) 
    67    !! $Id$ 
     67   !! $Id: usrdef_closea.F90 9124 2017-12-19 08:26:25Z gm $ 
    6868   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    6969   !!---------------------------------------------------------------------- 
     
    203203      !!---------------------------------------------------------------------- 
    204204      ! 
    205       IF( nn_timing == 1 )  CALL timing_start('sbc_clo') 
     205      IF( ln_timing )  CALL timing_start('sbc_clo') 
    206206      ! 
    207207      !                                                   !------------------!  
     
    328328      IF( jncse > 0 ) THEN 
    329329         ! 
    330          ! 3. Work out total fluxes over empmr source areas and add to empmr target areas. If jncse is zero does not loop.  
     330         ! 3. Work out total fluxes over empmr source areas and add to empmr target areas.  
    331331         ! 
    332332         DO jce = 1, jncse 
     
    387387      CALL lbc_lnk( emp , 'T', 1._wp ) 
    388388      ! 
    389       IF( nn_timing == 1 )  CALL timing_stop('sbc_clo') 
    390       ! 
    391389   END SUBROUTINE sbc_clo 
    392390 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/DOM/dom_oce.F90

    r9023 r9161  
    3131   !                                   !!* Namelist namdom : time & space domain * 
    3232   LOGICAL , PUBLIC ::   ln_linssh      !: =T  linear free surface ==>> model level are fixed in time 
    33    INTEGER , PUBLIC ::   nn_closea      !: =0 suppress closed sea/lake from the ORCA domain or not (=1) 
    3433   INTEGER , PUBLIC ::   nn_msh         !: >0  create a mesh-mask file (mesh_mask.nc) 
    3534   REAL(wp), PUBLIC ::   rn_isfhmin     !: threshold to discriminate grounded ice to floating ice 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/DOM/domain.F90

    r9124 r9161  
    3030   USE trc_oce        ! shared ocean & passive tracers variab 
    3131   USE phycst         ! physical constants 
    32    USE usrdef_closea  ! closed seas 
     32   USE closea         ! closed seas 
    3333   USE domhgr         ! domain: set the horizontal mesh 
    3434   USE domzgr         ! domain: set the vertical mesh 
     
    118118      CALL dom_glo                     ! global domain versus local domain 
    119119      CALL dom_nam                     ! read namelist ( namrun, namdom ) 
    120       CALL dom_clo( cn_cfg, nn_cfg )   ! Closed seas and lake 
    121120      CALL dom_hgr                     ! Horizontal mesh 
    122121      CALL dom_zgr( ik_top, ik_bot )   ! Vertical mesh and bathymetry 
    123       IF( nn_closea == 0 )   CALL clo_bat( ik_top, ik_bot )    !==  remove closed seas or lakes  ==! 
    124122      CALL dom_msk( ik_top, ik_bot )   ! Masks 
     123      IF( ln_closea ) CALL dom_clo     ! ln_closea=T : closed seas included in the simulation 
     124                                       ! Read in masks to define closed seas and lakes  
    125125      ! 
    126126      DO jj = 1, jpj                   ! depth of the iceshelves 
     
    274274         &             nn_stock, nn_write , ln_mskland  , ln_clobber   , nn_chunksz, nn_euler  ,     & 
    275275         &             ln_cfmeta, ln_iscpl 
    276       NAMELIST/namdom/ ln_linssh, nn_closea, nn_msh, rn_isfhmin, rn_rdt, rn_atfp, ln_crs 
     276      NAMELIST/namdom/ ln_linssh, nn_msh, rn_isfhmin, rn_rdt, rn_atfp, ln_crs 
    277277#if defined key_netcdf4 
    278278      NAMELIST/namnc4/ nn_nchunks_i, nn_nchunks_j, nn_nchunks_k, ln_nc4zip 
     
    383383         WRITE(numout,*) '   Namelist namdom : space & time domain' 
    384384         WRITE(numout,*) '      linear free surface (=T)              ln_linssh  = ', ln_linssh 
    385          WRITE(numout,*) '      suppression of closed seas (=0)       nn_closea  = ', nn_closea 
    386385         WRITE(numout,*) '      create mesh/mask file(s)              nn_msh     = ', nn_msh 
    387386         WRITE(numout,*) '           = 0   no file created           ' 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/DOM/domzgr.F90

    r9124 r9161  
    2929   USE dom_oce        ! ocean domain 
    3030   USE usrdef_zgr     ! user defined vertical coordinate system 
     31   USE closea         ! closed seas 
    3132   USE depth_e3       ! depth <=> e3 
    3233   USE wet_dry,   ONLY: ll_wd, ssh_ref  ! Wetting and drying 
     
    114115         gde3w_0(:,:,jk) = gde3w_0(:,:,jk-1) + e3w_0(:,:,jk) 
    115116      END DO 
     117      ! 
     118      ! Any closed seas (defined by closea_mask > 0 in domain_cfg file) to be filled  
     119      ! in at runtime if ln_closea=.false. 
     120      IF( .not. ln_closea ) CALL clo_bat( k_top, k_bot ) 
    116121      ! 
    117122      IF(lwp) THEN                     ! Control print 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r9124 r9161  
    5050   USE bdy_oce   , ONLY: ln_bdy 
    5151   USE usrdef_sbc     ! user defined: surface boundary condition 
    52    USE usrdef_closea  ! user defined: closed sea 
     52   USE closea         ! closed sea 
    5353   ! 
    5454   USE prtctl         ! Print control                    (prt_ctl routine) 
     
    151151         WRITE(numout,*) '         runoff / runoff mouths                     ln_rnf        = ', ln_rnf 
    152152         WRITE(numout,*) '         iceshelf formulation                       ln_isf        = ', ln_isf 
    153          WRITE(numout,*) '         closed sea (=0/1) (set in namdom)          nn_closea     = ', nn_closea 
    154153         WRITE(numout,*) '         nb of iterations if land-sea-mask applied  nn_lsm        = ', nn_lsm 
    155154         WRITE(numout,*) '         surface wave                               ln_wave       = ', ln_wave 
     
    435434      IF( nn_fwb    /= 0 )   CALL sbc_fwb( kt, nn_fwb, nn_fsbc )  ! control the freshwater budget 
    436435 
    437       ! treatment of closed sea in the model domain   (update freshwater fluxes) 
    438       ! Should not be ran if ln_diurnal_only 
    439       IF( .NOT.ln_diurnal_only .AND. nn_closea == 1 )   CALL sbc_clo( kt, cn_cfg, nn_cfg )    
     436      ! Special treatment of freshwater fluxes over closed seas in the model domain 
     437      ! Should not be run if ln_diurnal_only 
     438      IF( l_sbc_clo .AND. (.NOT. ln_diurnal_only) )   CALL sbc_clo( kt )    
    440439 
    441440!RBbug do not understand why see ticket 667 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/SBC/sbcrnf.F90

    r9125 r9161  
    2121   USE sbcisf         ! PM we could remove it I think 
    2222   USE eosbn2         ! Equation Of State 
    23    USE usrdef_closea  ! closed seas 
     23   USE closea         ! closed seas 
    2424   ! 
    2525   USE in_out_manager ! I/O manager 
     
    510510      CALL iom_close( inum )                                      ! close file 
    511511      ! 
    512       IF( nn_closea == 1 )   CALL clo_rnf( rnfmsk )               ! closed sea inflow set as ruver mouth 
     512      IF( l_clo_rnf )   CALL clo_rnf( rnfmsk )   ! closed sea inflow set as river mouth 
    513513      ! 
    514514      rnfmsk_z(:)   = 0._wp                                       ! vertical structure 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r9124 r9161  
    4848   USE phycst         ! physical constant                  (par_cst routine) 
    4949   USE domain         ! domain initialization   (dom_init & dom_cfg routines) 
     50   USE closea         ! treatment of closed seas (for ln_closea) 
    5051   USE usrdef_nam     ! user defined configuration 
    5152   USE tideini        ! tidal components initialization   (tide_ini routine) 
     
    242243         &             nn_isplt , nn_jsplt, nn_jctls, nn_jctle,   & 
    243244         &             ln_timing, ln_diacfl 
    244       NAMELIST/namcfg/ ln_read_cfg, cn_domcfg, ln_write_cfg, cn_domcfg_out, ln_use_jattr 
     245      NAMELIST/namcfg/ ln_read_cfg, cn_domcfg, ln_write_cfg, cn_domcfg_out, ln_use_jattr, ln_closea 
    245246      !!---------------------------------------------------------------------- 
    246247      ! 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/SAS_SRC/sbcssm.F90

    r9124 r9161  
    2323   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    2424   USE zpshde          ! z-coord. with partial steps: horizontal derivatives 
     25   USE closea          ! for ln_closea 
    2526   ! 
    2627   USE in_out_manager  ! I/O manager 
     
    224225         nn_fwb = 0 
    225226      ENDIF 
    226       IF( nn_closea > 0 ) THEN 
     227      IF( ln_closea ) THEN 
    227228         IF( lwp ) WRITE(numout,*) 'No closed seas adjustment needed with StandAlone Surface scheme' 
    228          nn_closea = 0 
     229         ln_closea = .false. 
    229230      ENDIF 
    230231      IF (l_sasread) THEN 
Note: See TracChangeset for help on using the changeset viewer.