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 @ 11295

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

add sbcclo.F90 + cleaning + comments

  • Property svn:keywords set to Id
File size: 12.1 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   !!   sbc_clo    : Special handling of freshwater fluxes over closed seas
19   !!   clo_rnf    : set close sea outflows as river mouths (see sbcrnf)
20   !!   clo_bat    : set to zero a field over closed sea (see domzgr)
21   !!----------------------------------------------------------------------
22   USE oce             ! dynamics and tracers
23   USE dom_oce         ! ocean space and time domain
24   USE phycst          ! physical constants
25   USE sbc_oce         ! ocean surface boundary conditions
26   USE iom             ! I/O routines
27   !
28   USE in_out_manager  ! I/O manager
29   USE lib_fortran,    ONLY: glob_sum
30   USE lbclnk          ! lateral boundary condition - MPP exchanges
31   USE lib_mpp         ! MPP library
32   USE timing          ! Timing
33
34   IMPLICIT NONE
35   PRIVATE read_csmask
36   PRIVATE alloc_csmask
37
38   PUBLIC dom_clo      ! called by domain module
39   PUBLIC clo_rnf      ! called by sbcrnf module
40   PUBLIC clo_bat      ! called in domzgr module
41
42   LOGICAL, PUBLIC :: ln_maskcs        !: logical to mask all closed sea
43   LOGICAL, PUBLIC :: ln_mask_csundef  !: logical to mask all undefined closed sea
44   LOGICAL, PUBLIC :: ln_clo_rnf       !: closed sea treated as runoff (update rnf mask)
45
46   LOGICAL, PUBLIC :: l_sbc_clo  !: T => net evap/precip over closed seas spread outover the globe/river mouth
47   LOGICAL, PUBLIC :: l_clo_rnf  !: T => Some closed seas output freshwater (RNF) to specified runoff points.
48
49   INTEGER, PUBLIC :: ncsg      !: number of closed seas global mappings (inferred from closea_mask_glo field)
50   INTEGER, PUBLIC :: ncsr      !: number of closed seas rnf    mappings (inferred from closea_mask_rnf field)
51   INTEGER, PUBLIC :: ncse      !: number of closed seas empmr  mappings (inferred from closea_mask_emp field)
52
53   INTEGER, PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:) :: mask_opnsea, mask_csundef !: mask defining the open sea and the undefined closed sea
54 
55   INTEGER, PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:) :: mask_csglo, mask_csgrpglo !: mask of integers defining closed seas
56   INTEGER, PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:) :: mask_csrnf, mask_csgrprnf !: mask of integers defining closed seas rnf mappings
57   INTEGER, PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:) :: mask_csemp, mask_csgrpemp !: mask of integers defining closed seas empmr mappings
58
59   !! * Substitutions
60#  include "vectopt_loop_substitute.h90"
61   !!----------------------------------------------------------------------
62   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
63   !! $Id$
64   !! Software governed by the CeCILL license (see ./LICENSE)
65   !!----------------------------------------------------------------------
66CONTAINS
67
68   SUBROUTINE dom_clo()
69      !!---------------------------------------------------------------------
70      !!                  ***  ROUTINE dom_clo  ***
71      !!       
72      !! ** Purpose :   Closed sea domain initialization
73      !!
74      !! ** Method  :   if a closed sea is located only in a model grid point
75      !!                just the thermodynamic processes are applied.
76      !!
77      !! ** Action  :   Read mask_cs* fields (if needed) from domain_cfg file and infer
78      !!                number of closed seas for each case (glo, rnf, emp) from mask_cs* field.
79      !!                mask_csglo and mask_csgrpglo  : integer values defining mappings from closed seas and associated groups to the open ocean for net fluxes.
80      !!                mask_csrnf and mask_csgrprnf  : integer values defining mappings from closed seas and associated groups to a runoff area for downwards flux only.
81      !!                mask_csemp and mask_csgrpemp  : integer values defining mappings from closed seas and associated groups to a runoff area for net fluxes.
82      !!----------------------------------------------------------------------
83      INTEGER ::   ios     ! io status
84      !!
85      NAMELIST/namclo/ ln_maskcs, ln_mask_csundef, ln_clo_rnf
86      !!---------------------------------------------------------------------
87      !!
88      REWIND( numnam_ref )              ! Namelist namclo in reference namelist : Lateral momentum boundary condition
89      READ  ( numnam_ref, namclo, IOSTAT = ios, ERR = 901 )
90901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namclo in reference namelist', lwp )
91      REWIND( numnam_cfg )              ! Namelist namclo in configuration namelist : Lateral momentum boundary condition
92      READ  ( numnam_cfg, namclo, IOSTAT = ios, ERR = 902 )
93902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namclo in configuration namelist', lwp )
94      IF(lwm) WRITE ( numond, namclo )
95      !!
96      IF(lwp) WRITE(numout,*)
97      IF(lwp) WRITE(numout,*)'dom_clo : read in masks to define closed seas '
98      IF(lwp) WRITE(numout,*)'~~~~~~~'
99      !!
100      !! check option compatibility
101      IF( .NOT. ln_read_cfg ) THEN
102         CALL ctl_stop('Suppression of closed seas does not work with ln_read_cfg = .true. . Set ln_closea = .false. .')
103      ENDIF
104      !!
105      IF( (.NOT. ln_maskcs) .AND. ln_diurnal_only ) THEN
106         CALL ctl_stop('Special handling of freshwater fluxes over closed seas not compatible with ln_diurnal_only.')
107      END IF
108      !
109      l_sbc_clo = .false. ; l_clo_rnf = .false.
110      IF (.NOT. ln_maskcs)                  l_sbc_clo = .true.
111      IF (.NOT. ln_maskcs .AND. ln_clo_rnf) l_clo_rnf = .true.
112      !
113      ! read the closed seas masks (if they exist) from domain_cfg file (if it exists)
114      ! ------------------------------------------------------------------------------
115      !
116      ! load mask of open sea and undefined closed seas
117      CALL alloc_csmask( mask_opnsea )
118      CALL read_csmask( cn_domcfg, 'mask_opensea' , mask_opnsea  )
119      !
120      IF ( ln_maskcs ) THEN
121         ! not special treatment of closed sea
122         l_sbc_clo = .false. ; l_clo_rnf = .false.
123      ELSE
124         ! special treatment of closed seas
125         l_sbc_clo = .true.
126         !
127         ! river mouth from lakes added to rnf mask for special treatment
128         IF ( ln_clo_rnf) l_clo_rnf = .true.
129         !
130         IF ( ln_mask_csundef) THEN
131            ! load undef cs mask (1 in undef closed sea)
132            CALL alloc_csmask( mask_csundef )
133            CALL read_csmask( cn_domcfg, 'mask_csundef', mask_csundef )
134            ! revert the mask for masking in domzgr
135            mask_csundef = 1 - mask_csundef
136         END IF
137         !
138         ! allocate source mask
139         CALL alloc_csmask( mask_csglo )
140         CALL alloc_csmask( mask_csrnf )
141         CALL alloc_csmask( mask_csemp )
142         !
143         ! load source mask of cs for each cases
144         CALL read_csmask( cn_domcfg, 'mask_csglo', mask_csglo )
145         CALL read_csmask( cn_domcfg, 'mask_csrnf', mask_csrnf )
146         CALL read_csmask( cn_domcfg, 'mask_csemp', mask_csemp )
147         !
148         ! compute number of cs for each cases
149         ncsg = MAXVAL( mask_csglo(:,:) ) ; CALL mpp_max( 'closea', ncsg )
150         ncsr = MAXVAL( mask_csrnf(:,:) ) ; CALL mpp_max( 'closea', ncsr )
151         ncse = MAXVAL( mask_csemp(:,:) ) ; CALL mpp_max( 'closea', ncse )
152         !
153         ! allocate closed sea group masks
154         CALL alloc_csmask( mask_csgrpglo )
155         CALL alloc_csmask( mask_csgrprnf )
156         CALL alloc_csmask( mask_csgrpemp )
157
158         ! load mask of cs group for each cases
159         CALL read_csmask( cn_domcfg, 'mask_csgrpglo', mask_csgrpglo )
160         CALL read_csmask( cn_domcfg, 'mask_csgrprnf', mask_csgrprnf )
161         CALL read_csmask( cn_domcfg, 'mask_csgrpemp', mask_csgrpemp )
162         !
163      END IF
164   END SUBROUTINE dom_clo
165
166   SUBROUTINE clo_rnf( p_rnfmsk )
167      !!---------------------------------------------------------------------
168      !!                  ***  ROUTINE clo_rnf  ***
169      !!                   
170      !! ** Purpose :   allow the treatment of closed sea outflow grid-points
171      !!                to be the same as river mouth grid-points
172      !!
173      !! ** Method  :   set to 1 the runoff mask (mskrnf, see sbcrnf module)
174      !!                at the closed sea outflow grid-point.
175      !!
176      !! ** Action  :   update (p_)mskrnf (set 1 at closed sea outflow)
177      !!----------------------------------------------------------------------
178      !!
179      !! subroutine parameter
180      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) ::   p_rnfmsk   ! river runoff mask (rnfmsk array)
181      !!
182      !! local variables
183      REAL(wp), DIMENSION(jpi,jpj) :: zmsk
184      !!----------------------------------------------------------------------
185      !
186      ! zmsk > 0 where cs river mouth defined (case rnf and emp)
187      zmsk(:,:) = ( mask_csgrprnf (:,:) + mask_csgrpemp(:,:) ) * mask_opnsea(:,:)
188      WHERE( zmsk(:,:) > 0 )
189         p_rnfmsk(:,:) = 1.0_wp
190      END WHERE
191      !
192   END SUBROUTINE clo_rnf
193     
194   SUBROUTINE clo_bat( k_top, k_bot, k_mask, cd_prt )
195      !!---------------------------------------------------------------------
196      !!                  ***  ROUTINE clo_bat  ***
197      !!                   
198      !! ** Purpose :   Suppress closed sea from the domain
199      !!
200      !! ** Method  :   Read in closea_mask field (if it exists) from domain_cfg file.
201      !!                Where closea_mask > 0 set first and last ocean level to 0
202      !!                (As currently coded you can't define a closea_mask field in
203      !!                usr_def_zgr).
204      !!
205      !! ** Action  :   set k_top=0 and k_bot=0 over closed seas
206      !!----------------------------------------------------------------------
207      !!
208      !! subroutine parameter
209      INTEGER, DIMENSION(:,:), INTENT(inout) ::   k_top, k_bot   ! ocean first and last level indices
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
212      !!
213      !! local variables
214      !!----------------------------------------------------------------------
215      !!
216      IF ( lwp ) THEN
217         WRITE(numout,*)
218         WRITE(numout,*) 'clo_bat : Suppression closed seas based on ',TRIM(cd_prt),' field.'
219         WRITE(numout,*) '~~~~~~~'
220         WRITE(numout,*)
221      ENDIF
222      !!
223      k_top(:,:) = k_top(:,:) * k_mask(:,:)
224      k_bot(:,:) = k_bot(:,:) * k_mask(:,:)
225      !!
226   END SUBROUTINE clo_bat
227
228   SUBROUTINE read_csmask(cd_file, cd_var, k_mskout)
229      !
230      ! subroutine parameter
231      CHARACTER(256), INTENT(in   ) :: cd_file, cd_var     ! netcdf file and variable name
232      INTEGER, DIMENSION(:,:), INTENT(inout) :: k_mskout ! output mask variable
233      !
234      ! local variables
235      INTEGER :: ics                       ! netcdf id
236      REAL(wp), DIMENSION(jpi,jpj) :: zdta ! netcdf data
237      !
238      CALL iom_open ( cd_file, ics )
239      CALL iom_get  ( ics, jpdom_data, TRIM(cd_var), zdta )
240      CALL iom_close( ics )
241      k_mskout(:,:) = NINT(zdta(:,:))
242      !
243   END SUBROUTINE read_csmask
244
245   SUBROUTINE alloc_csmask( kmask )
246      !
247      ! subroutine parameter
248      INTEGER, ALLOCATABLE, DIMENSION(:,:), INTENT(inout) :: kmask
249      !
250      ! local variables
251      INTEGER :: ierr
252      !
253      ALLOCATE( kmask(jpi,jpj) , STAT=ierr )
254      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'alloc_csmask: failed to allocate surf array')
255      !
256   END SUBROUTINE
257
258END MODULE closea
Note: See TracBrowser for help on using the repository browser.