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 branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/DOM – NEMO

source: branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/DOM/closea.F90 @ 9169

Last change on this file since 9169 was 9169, checked in by gm, 6 years ago

dev_merge_2017: all SRC: finalize the removal of useless warning when reading namelist_cfg + remove all nn_closea + nn_msh replaced by a logical

File size: 22.0 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   !!----------------------------------------------------------------------
14
15   !!----------------------------------------------------------------------
16   !!   dom_clo    : read in masks which define closed seas and runoff areas
17   !!   sbc_clo    : Special handling of freshwater fluxes over closed seas
18   !!   clo_rnf    : set close sea outflows as river mouths (see sbcrnf)
19   !!   clo_bat    : set to zero a field over closed sea (see domzgr)
20   !!----------------------------------------------------------------------
21   USE oce             ! dynamics and tracers
22   USE dom_oce         ! ocean space and time domain
23   USE phycst          ! physical constants
24   USE sbc_oce         ! ocean surface boundary conditions
25   USE iom             ! I/O routines
26   !
27   USE in_out_manager  ! I/O manager
28   USE lib_fortran,    ONLY: glob_sum
29   USE lbclnk          ! lateral boundary condition - MPP exchanges
30   USE lib_mpp         ! MPP library
31   USE timing          ! Timing
32
33   IMPLICIT NONE
34   PRIVATE
35
36   PUBLIC dom_clo      ! called by domain module
37   PUBLIC sbc_clo      ! called by sbcmod module
38   PUBLIC clo_rnf      ! called by sbcrnf module
39   PUBLIC clo_bat      ! called in domzgr module
40
41   LOGICAL, PUBLIC :: ln_closea  !:  T => keep closed seas (defined by closea_mask field) in the domain and apply
42                                 !:       special treatment of freshwater fluxes.
43                                 !:  F => suppress closed seas (defined by closea_mask field) from the bathymetry
44                                 !:       at runtime.
45                                 !:  If there is no closea_mask field in the domain_cfg file or we do not use
46                                 !:  a domain_cfg file then this logical does nothing.
47                                 !:
48   LOGICAL, PUBLIC :: l_sbc_clo  !: T => Closed seas defined, apply special treatment of freshwater fluxes.
49                                 !: F => No closed seas defined (closea_mask field not found).
50   LOGICAL, PUBLIC :: l_clo_rnf  !: T => Some closed seas output freshwater (RNF or EMPMR) to specified runoff points.
51   INTEGER, PUBLIC :: jncs       !: number of closed seas (inferred from closea_mask field)
52   INTEGER, PUBLIC :: jncsr      !: number of closed seas rnf mappings (inferred from closea_mask_rnf field)
53   INTEGER, PUBLIC :: jncse      !: number of closed seas empmr mappings (inferred from closea_mask_empmr field)
54   
55   INTEGER, PUBLIC, ALLOCATABLE, DIMENSION(:,:) ::  closea_mask       !: mask of integers defining closed seas
56   INTEGER, PUBLIC, ALLOCATABLE, DIMENSION(:,:) ::  closea_mask_rnf   !: mask of integers defining closed seas rnf mappings
57   INTEGER, PUBLIC, ALLOCATABLE, DIMENSION(:,:) ::  closea_mask_empmr !: mask of integers defining closed seas empmr mappings
58   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:)  ::   surf         !: closed sea surface areas
59                                                                  !: (and residual global surface area)
60   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:)  ::   surfr        !: closed sea target rnf surface areas
61   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:)  ::   surfe        !: closed sea target empmr surface areas
62
63   !! * Substitutions
64#  include "vectopt_loop_substitute.h90"
65   !!----------------------------------------------------------------------
66   !! NEMO/OPA 4.0 , NEMO Consortium (2016)
67   !! $Id: usrdef_closea.F90 9124 2017-12-19 08:26:25Z gm $
68   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
69   !!----------------------------------------------------------------------
70CONTAINS
71
72   SUBROUTINE dom_clo()
73      !!---------------------------------------------------------------------
74      !!                  ***  ROUTINE dom_clo  ***
75      !!       
76      !! ** Purpose :   Closed sea domain initialization
77      !!
78      !! ** Method  :   if a closed sea is located only in a model grid point
79      !!                just the thermodynamic processes are applied.
80      !!
81      !! ** Action  :   Read closea_mask* fields (if they exist) from domain_cfg file and infer
82      !!                number of closed seas from closea_mask field.
83      !!                closea_mask       : integer values defining closed seas (or groups of closed seas)
84      !!                closea_mask_rnf   : integer values defining mappings from closed seas or groups of
85      !!                                    closed seas to a runoff area for downwards flux only.
86      !!                closea_mask_empmr : integer values defining mappings from closed seas or groups of
87      !!                                    closed seas to a runoff area for net fluxes.
88      !!
89      !!                Python code to generate the closea_masks* fields from the old-style indices
90      !!                definitions is available at TOOLS/DOMAINcfg/make_closea_masks.py
91      !!----------------------------------------------------------------------
92      INTEGER ::   inum    ! input file identifier
93      INTEGER ::   ierr    ! error code
94      INTEGER ::   id      ! netcdf variable ID
95
96      REAL(wp), DIMENSION(jpi,jpj) :: zdata_in ! temporary real array for input
97      !!----------------------------------------------------------------------
98      !
99      IF(lwp) WRITE(numout,*)
100      IF(lwp) WRITE(numout,*)'dom_clo : read in masks to define closed seas '
101      IF(lwp) WRITE(numout,*)'~~~~~~~'
102      !
103      ! read the closed seas masks (if they exist) from domain_cfg file
104      ! ---------------------------------------------------------------
105      !
106      CALL iom_open( cn_domcfg, inum )
107
108      id = iom_varid(inum, 'closea_mask', ldstop = .false.)
109      IF( id > 0 ) THEN
110         l_sbc_clo = .true.
111         ALLOCATE( closea_mask(jpi,jpj) , STAT=ierr )
112         IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'dom_clo: failed to allocate closea_mask array')
113         zdata_in(:,:) = 0.0
114         CALL iom_get ( inum, jpdom_data, 'closea_mask', zdata_in )
115         closea_mask(:,:) = NINT(zdata_in(:,:)) * tmask(:,:,1)
116         ! number of closed seas = global maximum value in closea_mask field
117         jncs = maxval(closea_mask(:,:))
118         IF( lk_mpp ) CALL mpp_max(jncs)
119         IF( jncs > 0 ) THEN
120            IF( lwp ) WRITE(numout,*) 'Number of closed seas : ',jncs
121         ELSE
122            CALL ctl_stop( 'Problem with closea_mask field in domain_cfg file. Has no values > 0 so no closed seas defined.')
123         ENDIF
124      ELSE
125         IF( lwp ) WRITE(numout,*)
126         IF( lwp ) WRITE(numout,*) '   ==>>>   closea_mask field not found in domain_cfg file.'
127         IF( lwp ) WRITE(numout,*) '           No closed seas defined.'
128         IF( lwp ) WRITE(numout,*)
129         l_sbc_clo = .false.
130         jncs = 0 
131      ENDIF
132
133      l_clo_rnf = .false.
134
135      IF( l_sbc_clo ) THEN ! No point reading in closea_mask_rnf or closea_mask_empmr fields if no closed seas defined.
136
137         id = iom_varid(inum, 'closea_mask_rnf', ldstop = .false.)
138         IF( id > 0 ) THEN
139            l_clo_rnf = .true.           
140            ALLOCATE( closea_mask_rnf(jpi,jpj) , STAT=ierr )
141            IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'dom_clo: failed to allocate closea_mask_rnf array')
142            CALL iom_get ( inum, jpdom_data, 'closea_mask_rnf', zdata_in )
143            closea_mask_rnf(:,:) = NINT(zdata_in(:,:)) * tmask(:,:,1)
144            ! number of closed seas rnf mappings = global maximum in closea_mask_rnf field
145            jncsr = maxval(closea_mask_rnf(:,:))
146            IF( lk_mpp ) CALL mpp_max(jncsr)
147            IF( jncsr > 0 ) THEN
148               IF( lwp ) WRITE(numout,*) 'Number of closed seas rnf mappings : ',jncsr
149            ELSE
150               CALL ctl_stop( 'Problem with closea_mask_rnf field in domain_cfg file. Has no values > 0 so no closed seas rnf mappings defined.')
151            ENDIF
152         ELSE
153            IF( lwp ) WRITE(numout,*) 'closea_mask_rnf field not found in domain_cfg file. No closed seas rnf mappings defined.'
154            jncsr = 0
155         ENDIF
156 
157         id = iom_varid(inum, 'closea_mask_empmr', ldstop = .false.)
158         IF( id > 0 ) THEN
159            l_clo_rnf = .true.           
160            ALLOCATE( closea_mask_empmr(jpi,jpj) , STAT=ierr )
161            IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'dom_clo: failed to allocate closea_mask_empmr array')
162            CALL iom_get ( inum, jpdom_data, 'closea_mask_empmr', zdata_in )
163            closea_mask_empmr(:,:) = NINT(zdata_in(:,:)) * tmask(:,:,1)
164            ! number of closed seas empmr mappings = global maximum value in closea_mask_empmr field
165            jncse = maxval(closea_mask_empmr(:,:))
166            IF( lk_mpp ) CALL mpp_max(jncse)
167            IF( jncse > 0 ) THEN
168               IF( lwp ) WRITE(numout,*) 'Number of closed seas empmr mappings : ',jncse
169            ELSE
170               CALL ctl_stop( 'Problem with closea_mask_empmr field in domain_cfg file. Has no values > 0 so no closed seas empmr mappings defined.')
171            ENDIF
172         ELSE
173            IF( lwp ) WRITE(numout,*) 'closea_mask_empmr field not found in domain_cfg file. No closed seas empmr mappings defined.'
174            jncse = 0
175         ENDIF
176
177      ENDIF ! l_sbc_clo
178      !
179      CALL iom_close( inum )
180      !
181   END SUBROUTINE dom_clo
182
183
184   SUBROUTINE sbc_clo( kt )
185      !!---------------------------------------------------------------------
186      !!                  ***  ROUTINE sbc_clo  ***
187      !!                   
188      !! ** Purpose :   Special handling of closed seas
189      !!
190      !! ** Method  :   Water flux is forced to zero over closed sea
191      !!      Excess is shared between remaining ocean, or
192      !!      put as run-off in open ocean.
193      !!
194      !! ** Action  :   emp updated surface freshwater fluxes and associated heat content at kt
195      !!----------------------------------------------------------------------
196      INTEGER         , INTENT(in   ) ::   kt       ! ocean model time step
197      !
198      INTEGER             ::   ierr
199      INTEGER             ::   jc, jcr, jce   ! dummy loop indices
200      REAL(wp), PARAMETER ::   rsmall = 1.e-20_wp    ! Closed sea correction epsilon
201      REAL(wp)            ::   zfwf_total, zcoef, zcoef1         !
202      REAL(wp), DIMENSION(jncs)    ::   zfwf      !:
203      REAL(wp), DIMENSION(jncsr+1) ::   zfwfr     !: freshwater fluxes over closed seas
204      REAL(wp), DIMENSION(jncse+1) ::   zfwfe     !:
205      REAL(wp), DIMENSION(jpi,jpj) ::   ztmp2d   ! 2D workspace
206      !!----------------------------------------------------------------------
207      !
208      IF( ln_timing )  CALL timing_start('sbc_clo')
209      !
210      !                                                   !------------------!
211      IF( kt == nit000 ) THEN                             !  Initialisation  !
212         !                                                !------------------!
213         IF(lwp) WRITE(numout,*)
214         IF(lwp) WRITE(numout,*)'sbc_clo : closed seas '
215         IF(lwp) WRITE(numout,*)'~~~~~~~'
216
217         ALLOCATE( surf(jncs+1) , STAT=ierr )
218         IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'sbc_clo: failed to allocate surf array')
219         surf(:) = 0.e0_wp
220         !
221         ! jncsr can be zero so add 1 to avoid allocating zero-length array
222         ALLOCATE( surfr(jncsr+1) , STAT=ierr )
223         IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'sbc_clo: failed to allocate surfr array')
224         surfr(:) = 0.e0_wp
225         !
226         ! jncse can be zero so add 1 to avoid allocating zero-length array
227         ALLOCATE( surfe(jncse+1) , STAT=ierr )
228         IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'sbc_clo: failed to allocate surfe array')
229         surfe(:) = 0.e0_wp
230         !
231         surf(jncs+1) = glob_sum( e1e2t(:,:) )   ! surface of the global ocean
232         !
233         !                                        ! surface areas of closed seas
234         DO jc = 1, jncs
235            ztmp2d(:,:) = 0.e0_wp
236            WHERE( closea_mask(:,:) == jc ) ztmp2d(:,:) = e1e2t(:,:) * tmask_i(:,:)
237            surf(jc) = glob_sum( ztmp2d(:,:) )
238         END DO
239         !
240         ! jncs+1 : surface area of global ocean, closed seas excluded
241         surf(jncs+1) = surf(jncs+1) - SUM(surf(1:jncs))
242         !
243         !                                        ! surface areas of rnf target areas
244         IF( jncsr > 0 ) THEN
245            DO jcr = 1, jncsr
246               ztmp2d(:,:) = 0.e0_wp
247               WHERE( closea_mask_rnf(:,:) == jcr .and. closea_mask(:,:) == 0 ) ztmp2d(:,:) = e1e2t(:,:) * tmask_i(:,:)
248               surfr(jcr) = glob_sum( ztmp2d(:,:) )
249            END DO
250         ENDIF
251         !
252         !                                        ! surface areas of empmr target areas
253         IF( jncse > 0 ) THEN
254            DO jce = 1, jncse
255               ztmp2d(:,:) = 0.e0_wp
256               WHERE( closea_mask_empmr(:,:) == jce .and. closea_mask(:,:) == 0 ) ztmp2d(:,:) = e1e2t(:,:) * tmask_i(:,:)
257               surfe(jce) = glob_sum( ztmp2d(:,:) )
258            END DO
259         ENDIF
260         !
261         IF(lwp) WRITE(numout,*)'     Closed sea surface areas (km2)'
262         DO jc = 1, jncs
263            IF(lwp) WRITE(numout,FMT='(1I3,5X,ES12.2)') jc, surf(jc) * 1.0e-6
264         END DO
265         IF(lwp) WRITE(numout,FMT='(A,ES12.2)') 'Global surface area excluding closed seas (km2): ', surf(jncs+1) * 1.0e-6
266         !
267         IF(jncsr > 0) THEN
268            IF(lwp) WRITE(numout,*)'     Closed sea target rnf surface areas (km2)'
269            DO jcr = 1, jncsr
270               IF(lwp) WRITE(numout,FMT='(1I3,5X,ES12.2)') jcr, surfr(jcr) * 1.0e-6
271            END DO
272         ENDIF
273         !
274         IF(jncse > 0) THEN
275            IF(lwp) WRITE(numout,*)'     Closed sea target empmr surface areas (km2)'
276            DO jce = 1, jncse
277               IF(lwp) WRITE(numout,FMT='(1I3,5X,ES12.2)') jce, surfe(jce) * 1.0e-6
278            END DO
279         ENDIF
280      ENDIF
281      !
282      !                                                      !--------------------!
283      !                                                      !  update emp        !
284      !                                                      !--------------------!
285
286      zfwf_total = 0._wp
287
288      !
289      ! 1. Work out total freshwater fluxes over closed seas from EMP - RNF.
290      !
291      zfwf(:) = 0.e0_wp           
292      DO jc = 1, jncs
293         ztmp2d(:,:) = 0.e0_wp
294         WHERE( closea_mask(:,:) == jc ) ztmp2d(:,:) = e1e2t(:,:) * ( emp(:,:)-rnf(:,:) ) * tmask_i(:,:)
295         zfwf(jc) = glob_sum( ztmp2d(:,:) )
296      END DO
297      zfwf_total = SUM(zfwf)
298
299      zfwfr(:) = 0.e0_wp           
300      IF( jncsr > 0 ) THEN
301         !
302         ! 2. Work out total FW fluxes over rnf source areas and add to rnf target areas.
303         !    Where zfwf is negative add flux at specified runoff points and subtract from fluxes for global redistribution.
304         !    Where positive leave in global redistribution total.
305         !
306         DO jcr = 1, jncsr
307            !
308            ztmp2d(:,:) = 0.e0_wp
309            WHERE( closea_mask_rnf(:,:) == jcr .and. closea_mask(:,:) > 0 ) ztmp2d(:,:) = e1e2t(:,:) * ( emp(:,:)-rnf(:,:) ) * tmask_i(:,:)
310            zfwfr(jcr) = glob_sum( ztmp2d(:,:) )
311            !
312            ! The following if avoids the redistribution of the round off
313            IF ( ABS(zfwfr(jcr) / surf(jncs+1) ) > rsmall) THEN
314               !
315               ! Add residuals to target runoff points if negative and subtract from total to be added globally
316               IF( zfwfr(jcr) < 0.0 ) THEN
317                  zfwf_total = zfwf_total - zfwfr(jcr)
318                  zcoef    = zfwfr(jcr) / surfr(jcr)
319                  zcoef1   = rcp * zcoef
320                  WHERE( closea_mask_rnf(:,:) == jcr .and. closea_mask(:,:) == 0.0)
321                     emp(:,:) = emp(:,:) + zcoef
322                     qns(:,:) = qns(:,:) - zcoef1 * sst_m(:,:)
323                  ENDWHERE
324               ENDIF
325               !
326            ENDIF
327         END DO
328      ENDIF  ! jncsr > 0   
329      !
330      zfwfe(:) = 0.e0_wp           
331      IF( jncse > 0 ) THEN
332         !
333         ! 3. Work out total fluxes over empmr source areas and add to empmr target areas.
334         !
335         DO jce = 1, jncse
336            !
337            ztmp2d(:,:) = 0.e0_wp
338            WHERE( closea_mask_empmr(:,:) == jce .and. closea_mask(:,:) > 0 ) ztmp2d(:,:) = e1e2t(:,:) * ( emp(:,:)-rnf(:,:) ) * tmask_i(:,:)
339            zfwfe(jce) = glob_sum( ztmp2d(:,:) )
340            !
341            ! The following if avoids the redistribution of the round off
342            IF ( ABS( zfwfe(jce) / surf(jncs+1) ) > rsmall ) THEN
343               !
344               ! Add residuals to runoff points and subtract from total to be added globally
345               zfwf_total = zfwf_total - zfwfe(jce)
346               zcoef    = zfwfe(jce) / surfe(jce)
347               zcoef1   = rcp * zcoef
348               WHERE( closea_mask_empmr(:,:) == jce .and. closea_mask(:,:) == 0.0)
349                  emp(:,:) = emp(:,:) + zcoef
350                  qns(:,:) = qns(:,:) - zcoef1 * sst_m(:,:)
351               ENDWHERE
352               !
353            ENDIF
354         END DO
355      ENDIF ! jncse > 0   
356
357      !
358      ! 4. Spread residual flux over global ocean.
359      !
360      ! The following if avoids the redistribution of the round off
361      IF ( ABS(zfwf_total / surf(jncs+1) ) > rsmall) THEN
362         zcoef    = zfwf_total / surf(jncs+1)
363         zcoef1   = rcp * zcoef
364         WHERE( closea_mask(:,:) == 0 )
365            emp(:,:) = emp(:,:) + zcoef
366            qns(:,:) = qns(:,:) - zcoef1 * sst_m(:,:)
367         ENDWHERE
368      ENDIF
369
370      !
371      ! 5. Subtract area means from emp (and qns) over closed seas to give zero mean FW flux over each sea.
372      !
373      DO jc = 1, jncs
374         ! The following if avoids the redistribution of the round off
375         IF ( ABS(zfwf(jc) / surf(jncs+1) ) > rsmall) THEN
376            !
377            ! Subtract residuals from fluxes over closed sea
378            zcoef    = zfwf(jc) / surf(jc)
379            zcoef1   = rcp * zcoef
380            WHERE( closea_mask(:,:) == jc )
381               emp(:,:) = emp(:,:) - zcoef
382               qns(:,:) = qns(:,:) + zcoef1 * sst_m(:,:)
383            ENDWHERE
384            !
385         ENDIF
386      END DO
387      !
388      emp (:,:) = emp (:,:) * tmask(:,:,1)
389      !
390      CALL lbc_lnk( emp , 'T', 1._wp )
391      !
392   END SUBROUTINE sbc_clo
393
394   SUBROUTINE clo_rnf( p_rnfmsk )
395      !!---------------------------------------------------------------------
396      !!                  ***  ROUTINE sbc_rnf  ***
397      !!                   
398      !! ** Purpose :   allow the treatment of closed sea outflow grid-points
399      !!                to be the same as river mouth grid-points
400      !!
401      !! ** Method  :   set to 1 the runoff mask (mskrnf, see sbcrnf module)
402      !!                at the closed sea outflow grid-point.
403      !!
404      !! ** Action  :   update (p_)mskrnf (set 1 at closed sea outflow)
405      !!----------------------------------------------------------------------
406      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) ::   p_rnfmsk   ! river runoff mask (rnfmsk array)
407      !!----------------------------------------------------------------------
408      !
409      IF( jncsr > 0 ) THEN
410         WHERE( closea_mask_rnf(:,:) > 0 .and. closea_mask(:,:) == 0 )
411            p_rnfmsk(:,:) = MAX( p_rnfmsk(:,:), 1.0_wp )
412         ENDWHERE
413      ENDIF
414      !
415      IF( jncse > 0 ) THEN
416         WHERE( closea_mask_empmr(:,:) > 0 .and. closea_mask(:,:) == 0 )
417            p_rnfmsk(:,:) = MAX( p_rnfmsk(:,:), 1.0_wp )
418         ENDWHERE
419      ENDIF
420      !
421   END SUBROUTINE clo_rnf
422   
423     
424   SUBROUTINE clo_bat( k_top, k_bot )
425      !!---------------------------------------------------------------------
426      !!                  ***  ROUTINE clo_bat  ***
427      !!                   
428      !! ** Purpose :   Suppress closed sea from the domain
429      !!
430      !! ** Method  :   Read in closea_mask field (if it exists) from domain_cfg file.
431      !!                Where closea_mask > 0 set first and last ocean level to 0
432      !!                (As currently coded you can't define a closea_mask field in
433      !!                usr_def_zgr).
434      !!
435      !! ** Action  :   set k_top=0 and k_bot=0 over closed seas
436      !!----------------------------------------------------------------------
437      INTEGER, DIMENSION(:,:), INTENT(inout) ::   k_top, k_bot   ! ocean first and last level indices
438      INTEGER                           :: inum, id
439      INTEGER,  DIMENSION(jpi,jpj) :: closea_mask ! closea_mask field
440      REAL(wp), DIMENSION(jpi,jpj) :: zdata_in ! temporary real array for input
441      !!----------------------------------------------------------------------
442      !
443      IF(lwp) THEN                     ! Control print
444         WRITE(numout,*)
445         WRITE(numout,*) 'clo_bat : suppression of closed seas'
446         WRITE(numout,*) '~~~~~~~'
447      ENDIF
448      !
449      CALL iom_open( cn_domcfg, inum )
450      !
451      id = iom_varid(inum, 'closea_mask', ldstop = .false.)     
452      IF( id > 0 ) THEN
453         IF( lwp ) WRITE(numout,*) 'Suppressing closed seas in bathymetry based on closea_mask field,'
454         CALL iom_get ( inum, jpdom_data, 'closea_mask', zdata_in )
455         closea_mask(:,:) = NINT(zdata_in(:,:))
456         WHERE( closea_mask(:,:) > 0 )
457            k_top(:,:) = 0   
458            k_bot(:,:) = 0   
459         ENDWHERE
460      ELSE
461         IF( lwp ) WRITE(numout,*) 'No closea_mask field found in domain_cfg file. No suppression of closed seas.'
462      ENDIF
463      !
464      ! Initialise l_sbc_clo and l_clo_rnf for this case (ln_closea=.false.)
465      l_sbc_clo = .false.
466      l_clo_rnf = .false.
467      !
468      CALL iom_close(inum)
469      !
470   END SUBROUTINE clo_bat
471
472   !!======================================================================
473END MODULE closea
474
Note: See TracBrowser for help on using the repository browser.