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.
closea.F90 in NEMO/branches/2019/ENHANCE-03_closea/src/OCE/DOM – NEMO

source: NEMO/branches/2019/ENHANCE-03_closea/src/OCE/DOM/closea.F90 @ 11656

Last change on this file since 11656 was 11656, checked in by mathiot, 5 years ago

ENHANCE-03_closea: add heat/fw fluxes output from closed seas + rm useless USE statements + add USE ONLY when reasonable + ensure heat conservation during the redistribution process (ticket #2143)

  • Property svn:keywords set to Id
File size: 13.2 KB
RevLine 
[9017]1MODULE closea
[3]2   !!======================================================================
[9155]3   !!                   ***  MODULE  closea  ***
[6923]4   !!
[6717]5   !! User define : specific treatments associated with closed seas
[3]6   !!======================================================================
[6717]7   !! History :   8.2  !  2000-05  (O. Marti)  Original code
8   !!   NEMO      1.0  !  2002-06  (E. Durand, G. Madec)  F90
9   !!             3.0  !  2006-07  (G. Madec)  add clo_rnf, clo_ups, clo_bat
10   !!             3.4  !  2014-12  (P.G. Fogli) sbc_clo bug fix & mpp reproducibility
11   !!             4.0  !  2016-06  (G. Madec)  move to usrdef_closea, remove clo_ups
[9017]12   !!             4.0  !  2017-12  (D. Storkey) new formulation based on masks read from file
[11207]13   !!             4.1  !  2019-07  (P. Mathiot) update to the new domcfg.nc input file
[888]14   !!----------------------------------------------------------------------
[3]15
16   !!----------------------------------------------------------------------
[9078]17   !!   dom_clo    : read in masks which define closed seas and runoff areas
[888]18   !!   clo_rnf    : set close sea outflows as river mouths (see sbcrnf)
[11629]19   !!   clo_msk    : set to zero a field over closed sea (see domzgr)
[3]20   !!----------------------------------------------------------------------
[11656]21   USE in_out_manager  ! I/O manager
[6717]22   !
[11656]23   USE diurnal_bulk, ONLY: ln_diurnal_only            ! used for sanity check
24   USE iom         , ONLY: iom_open, iom_get, iom_close, jpdom_data ! I/O routines
25   USE lib_fortran , ONLY: glob_sum                   ! fortran library
26   USE lib_mpp     , ONLY: mpp_max, ctl_nam, ctl_stop ! MPP library
[3]27
28   IMPLICIT NONE
29
[11656]30   PRIVATE
31
[7200]32   PUBLIC dom_clo      ! called by domain module
33   PUBLIC clo_rnf      ! called by sbcrnf module
[11629]34   PUBLIC clo_msk      ! called in domzgr module
[3]35
[11295]36   LOGICAL, PUBLIC :: ln_maskcs        !: logical to mask all closed sea
37   LOGICAL, PUBLIC :: ln_mask_csundef  !: logical to mask all undefined closed sea
38   LOGICAL, PUBLIC :: ln_clo_rnf       !: closed sea treated as runoff (update rnf mask)
[3]39
[11207]40   LOGICAL, PUBLIC :: l_sbc_clo  !: T => net evap/precip over closed seas spread outover the globe/river mouth
41   LOGICAL, PUBLIC :: l_clo_rnf  !: T => Some closed seas output freshwater (RNF) to specified runoff points.
42
[11295]43   INTEGER, PUBLIC :: ncsg      !: number of closed seas global mappings (inferred from closea_mask_glo field)
44   INTEGER, PUBLIC :: ncsr      !: number of closed seas rnf    mappings (inferred from closea_mask_rnf field)
45   INTEGER, PUBLIC :: ncse      !: number of closed seas empmr  mappings (inferred from closea_mask_emp field)
[11207]46
[11656]47   INTEGER, PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:) :: mask_opnsea, mask_csundef  !: mask defining the open sea and the undefined closed sea
[11207]48 
[11656]49   INTEGER, PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:) :: mask_csglo , mask_csgrpglo !: mask of integers defining closed seas
50   INTEGER, PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:) :: mask_csrnf , mask_csgrprnf !: mask of integers defining closed seas rnf mappings
51   INTEGER, PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:) :: mask_csemp , mask_csgrpemp !: mask of integers defining closed seas empmr mappings
[11207]52
[3]53   !! * Substitutions
54#  include "vectopt_loop_substitute.h90"
55   !!----------------------------------------------------------------------
[9598]56   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
[10069]57   !! $Id$
[10068]58   !! Software governed by the CeCILL license (see ./LICENSE)
[3]59   !!----------------------------------------------------------------------
60CONTAINS
61
[9078]62   SUBROUTINE dom_clo()
[3]63      !!---------------------------------------------------------------------
64      !!                  ***  ROUTINE dom_clo  ***
65      !!       
66      !! ** Purpose :   Closed sea domain initialization
67      !!
68      !! ** Method  :   if a closed sea is located only in a model grid point
[888]69      !!                just the thermodynamic processes are applied.
[3]70      !!
[11207]71      !! ** Action  :   Read mask_cs* fields (if needed) from domain_cfg file and infer
72      !!                number of closed seas for each case (glo, rnf, emp) from mask_cs* field.
[11629]73      !!
74      !! ** Output  :   mask_csglo and mask_csgrpglo  : integer values defining mappings from closed seas and associated groups to the open ocean for net fluxes.
[11207]75      !!                mask_csrnf and mask_csgrprnf  : integer values defining mappings from closed seas and associated groups to a runoff area for downwards flux only.
76      !!                mask_csemp and mask_csgrpemp  : integer values defining mappings from closed seas and associated groups to a runoff area for net fluxes.
77      !!----------------------------------------------------------------------
78      INTEGER ::   ios     ! io status
[9017]79      !!
[11207]80      NAMELIST/namclo/ ln_maskcs, ln_mask_csundef, ln_clo_rnf
81      !!---------------------------------------------------------------------
82      !!
83      REWIND( numnam_ref )              ! Namelist namclo in reference namelist : Lateral momentum boundary condition
84      READ  ( numnam_ref, namclo, IOSTAT = ios, ERR = 901 )
85901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namclo in reference namelist', lwp )
86      REWIND( numnam_cfg )              ! Namelist namclo in configuration namelist : Lateral momentum boundary condition
87      READ  ( numnam_cfg, namclo, IOSTAT = ios, ERR = 902 )
88902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namclo in configuration namelist', lwp )
89      IF(lwm) WRITE ( numond, namclo )
90      !!
[3]91      IF(lwp) WRITE(numout,*)
[9078]92      IF(lwp) WRITE(numout,*)'dom_clo : read in masks to define closed seas '
[64]93      IF(lwp) WRITE(numout,*)'~~~~~~~'
[11656]94      IF(lwp) WRITE(numout,*)
[11207]95      !!
96      !! check option compatibility
97      IF( .NOT. ln_read_cfg ) THEN
98         CALL ctl_stop('Suppression of closed seas does not work with ln_read_cfg = .true. . Set ln_closea = .false. .')
99      ENDIF
100      !!
101      IF( (.NOT. ln_maskcs) .AND. ln_diurnal_only ) THEN
102         CALL ctl_stop('Special handling of freshwater fluxes over closed seas not compatible with ln_diurnal_only.')
103      END IF
[5836]104      !
[9209]105      ! read the closed seas masks (if they exist) from domain_cfg file (if it exists)
106      ! ------------------------------------------------------------------------------
[5836]107      !
[11207]108      ! load mask of open sea and undefined closed seas
109      CALL alloc_csmask( mask_opnsea )
110      CALL read_csmask( cn_domcfg, 'mask_opensea' , mask_opnsea  )
111      !
112      IF ( ln_maskcs ) THEN
[11629]113         ! closed sea are masked
[11656]114         IF(lwp) WRITE(numout,*)'          ln_maskcs = T : all closed seas are masked'
115         IF(lwp) WRITE(numout,*)
[11629]116         ! no special treatment of closed sea
117         ! no redistribution of emp unbalance over closed sea into river mouth/open ocean
[11207]118         l_sbc_clo = .false. ; l_clo_rnf = .false.
119      ELSE
[11629]120         ! redistribution of emp unbalance over closed sea into river mouth/open ocean
[11656]121         IF(lwp) WRITE(numout,*)'          ln_maskcs = F : net emp is corrected over defined closed seas'
122         !
[11207]123         l_sbc_clo = .true.
[9209]124         !
[11207]125         ! river mouth from lakes added to rnf mask for special treatment
126         IF ( ln_clo_rnf) l_clo_rnf = .true.
[9209]127         !
[11207]128         IF ( ln_mask_csundef) THEN
[11656]129            ! closed sea not defined (ie not in the domcfg namelist used to build the domcfg.nc file) are masked
130            IF(lwp) WRITE(numout,*)'          ln_mask_csundef = T : all undefined closed seas are masked'
131            !
[11207]132            CALL alloc_csmask( mask_csundef )
133            CALL read_csmask( cn_domcfg, 'mask_csundef', mask_csundef )
[11629]134            ! revert the mask for masking of undefined closed seas in domzgr
135            ! (0 over the undefined closed sea and 1 elsewhere)
[11656]136            mask_csundef(:,:) = 1 - mask_csundef(:,:)
[11207]137         END IF
[11656]138         IF(lwp) WRITE(numout,*)
[11207]139         !
[11629]140         ! allocate source mask for each cases
[11207]141         CALL alloc_csmask( mask_csglo )
142         CALL alloc_csmask( mask_csrnf )
143         CALL alloc_csmask( mask_csemp )
144         !
145         ! load source mask of cs for each cases
146         CALL read_csmask( cn_domcfg, 'mask_csglo', mask_csglo )
147         CALL read_csmask( cn_domcfg, 'mask_csrnf', mask_csrnf )
148         CALL read_csmask( cn_domcfg, 'mask_csemp', mask_csemp )
149         !
150         ! compute number of cs for each cases
[11295]151         ncsg = MAXVAL( mask_csglo(:,:) ) ; CALL mpp_max( 'closea', ncsg )
152         ncsr = MAXVAL( mask_csrnf(:,:) ) ; CALL mpp_max( 'closea', ncsr )
153         ncse = MAXVAL( mask_csemp(:,:) ) ; CALL mpp_max( 'closea', ncse )
[11207]154         !
[11629]155         ! allocate closed sea group masks
156         !(used to defined the target area in case multiple lakes have the same river mouth (great lakes for example)
[11207]157         CALL alloc_csmask( mask_csgrpglo )
158         CALL alloc_csmask( mask_csgrprnf )
159         CALL alloc_csmask( mask_csgrpemp )
[9017]160
[11207]161         ! load mask of cs group for each cases
162         CALL read_csmask( cn_domcfg, 'mask_csgrpglo', mask_csgrpglo )
163         CALL read_csmask( cn_domcfg, 'mask_csgrprnf', mask_csgrprnf )
164         CALL read_csmask( cn_domcfg, 'mask_csgrpemp', mask_csgrpemp )
165         !
166      END IF
167   END SUBROUTINE dom_clo
[9017]168
[888]169   SUBROUTINE clo_rnf( p_rnfmsk )
170      !!---------------------------------------------------------------------
[11207]171      !!                  ***  ROUTINE clo_rnf  ***
[888]172      !!                   
173      !! ** Purpose :   allow the treatment of closed sea outflow grid-points
174      !!                to be the same as river mouth grid-points
175      !!
176      !! ** Method  :   set to 1 the runoff mask (mskrnf, see sbcrnf module)
177      !!                at the closed sea outflow grid-point.
178      !!
179      !! ** Action  :   update (p_)mskrnf (set 1 at closed sea outflow)
180      !!----------------------------------------------------------------------
[11207]181      !! subroutine parameter
[888]182      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) ::   p_rnfmsk   ! river runoff mask (rnfmsk array)
[11207]183      !!
184      !! local variables
185      REAL(wp), DIMENSION(jpi,jpj) :: zmsk
[888]186      !!----------------------------------------------------------------------
187      !
[11207]188      ! zmsk > 0 where cs river mouth defined (case rnf and emp)
189      zmsk(:,:) = ( mask_csgrprnf (:,:) + mask_csgrpemp(:,:) ) * mask_opnsea(:,:)
190      WHERE( zmsk(:,:) > 0 )
191         p_rnfmsk(:,:) = 1.0_wp
192      END WHERE
[888]193      !
194   END SUBROUTINE clo_rnf
195     
[11629]196   SUBROUTINE clo_msk( k_top, k_bot, k_mask, cd_prt )
[888]197      !!---------------------------------------------------------------------
[11629]198      !!                  ***  ROUTINE clo_msk  ***
[888]199      !!                   
[9078]200      !! ** Purpose :   Suppress closed sea from the domain
[888]201      !!
[11629]202      !! ** Method  :   Where closea_mask > 0 set first and last ocean level to 0
[9078]203      !!                (As currently coded you can't define a closea_mask field in
204      !!                usr_def_zgr).
[888]205      !!
[9078]206      !! ** Action  :   set k_top=0 and k_bot=0 over closed seas
[888]207      !!----------------------------------------------------------------------
[11207]208      !! subroutine parameter
[6717]209      INTEGER, DIMENSION(:,:), INTENT(inout) ::   k_top, k_bot   ! ocean first and last level indices
[11295]210      INTEGER, DIMENSION(:,:), INTENT(in   ) ::   k_mask         ! mask used to mask ktop and k_bot
211      CHARACTER(256),          INTENT(in   ) ::   cd_prt         ! text for control print
[11207]212      !!
213      !! local variables
[888]214      !!----------------------------------------------------------------------
[11207]215      !!
216      IF ( lwp ) THEN
[9078]217         WRITE(numout,*)
[11629]218         WRITE(numout,*) 'clo_msk : Suppression closed seas based on ',TRIM(cd_prt),' field.'
[9078]219         WRITE(numout,*) '~~~~~~~'
[11207]220         WRITE(numout,*)
[9078]221      ENDIF
[11207]222      !!
[11295]223      k_top(:,:) = k_top(:,:) * k_mask(:,:)
224      k_bot(:,:) = k_bot(:,:) * k_mask(:,:)
[11207]225      !!
[11629]226   END SUBROUTINE clo_msk
[11207]227
[11295]228   SUBROUTINE read_csmask(cd_file, cd_var, k_mskout)
[11629]229      !!---------------------------------------------------------------------
230      !!                  ***  ROUTINE read_csmask  ***
231      !!                   
232      !! ** Purpose : read mask in cd_filec file
233      !!----------------------------------------------------------------------
[11207]234      ! subroutine parameter
[11629]235      CHARACTER(256),          INTENT(in   ) :: cd_file, cd_var     ! netcdf file and variable name
236      INTEGER, DIMENSION(:,:), INTENT(  out) :: k_mskout            ! output mask variable
[9078]237      !
[11207]238      ! local variables
[11295]239      INTEGER :: ics                       ! netcdf id
240      REAL(wp), DIMENSION(jpi,jpj) :: zdta ! netcdf data
[11629]241      !!----------------------------------------------------------------------
[9078]242      !
[11295]243      CALL iom_open ( cd_file, ics )
244      CALL iom_get  ( ics, jpdom_data, TRIM(cd_var), zdta )
[11207]245      CALL iom_close( ics )
[11295]246      k_mskout(:,:) = NINT(zdta(:,:))
[11207]247      !
248   END SUBROUTINE read_csmask
[3]249
[11295]250   SUBROUTINE alloc_csmask( kmask )
[11629]251      !!---------------------------------------------------------------------
252      !!                  ***  ROUTINE alloc_csmask  ***
253      !!                   
254      !! ** Purpose : allocated cs mask
255      !!----------------------------------------------------------------------
[11207]256      ! subroutine parameter
[11295]257      INTEGER, ALLOCATABLE, DIMENSION(:,:), INTENT(inout) :: kmask
[11207]258      !
259      ! local variables
260      INTEGER :: ierr
[11629]261      !!----------------------------------------------------------------------
[11207]262      !
[11295]263      ALLOCATE( kmask(jpi,jpj) , STAT=ierr )
[11207]264      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'alloc_csmask: failed to allocate surf array')
265      !
266   END SUBROUTINE
267
[9017]268END MODULE closea
Note: See TracBrowser for help on using the repository browser.