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/trunk/src/OCE/DOM – NEMO

source: NEMO/trunk/src/OCE/DOM/closea.F90 @ 12377

Last change on this file since 12377 was 12377, checked in by acc, 4 years ago

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

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