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/UKMO/NEMO_4.0_mirror_text_diagnostics/src/OCE/DOM – NEMO

source: NEMO/branches/UKMO/NEMO_4.0_mirror_text_diagnostics/src/OCE/DOM/closea.F90 @ 10986

Last change on this file since 10986 was 10986, checked in by andmirek, 5 years ago

GMED 462 add flush

File size: 23.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   !!----------------------------------------------------------------------
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/OCE 4.0 , NEMO Consortium (2018)
67   !! $Id$
68   !! Software governed by the CeCILL license (see ./LICENSE)
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) THEN
100         WRITE(numout,*)
101         WRITE(numout,*)'dom_clo : read in masks to define closed seas '
102         WRITE(numout,*)'~~~~~~~'
103         IF(lflush) CALL FLUSH(numout)
104      ENDIF
105      !
106      ! read the closed seas masks (if they exist) from domain_cfg file (if it exists)
107      ! ------------------------------------------------------------------------------
108      !
109      IF( ln_read_cfg) THEN
110         !
111         CALL iom_open( cn_domcfg, inum )
112         !
113         id = iom_varid(inum, 'closea_mask', ldstop = .false.)
114         IF( id > 0 ) THEN
115            l_sbc_clo = .true.
116            ALLOCATE( closea_mask(jpi,jpj) , STAT=ierr )
117            IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'dom_clo: failed to allocate closea_mask array')
118            zdata_in(:,:) = 0.0
119            CALL iom_get ( inum, jpdom_data, 'closea_mask', zdata_in )
120            closea_mask(:,:) = NINT(zdata_in(:,:)) * tmask(:,:,1)
121            ! number of closed seas = global maximum value in closea_mask field
122            jncs = maxval(closea_mask(:,:))
123            CALL mpp_max('closea', jncs)
124            IF( jncs > 0 ) THEN
125               IF( lwp ) THEN
126                  WRITE(numout,*) 'Number of closed seas : ',jncs
127                  IF(lflush) CALL FLUSH(numout)
128               ENDIF
129            ELSE
130               CALL ctl_stop( 'Problem with closea_mask field in domain_cfg file. Has no values > 0 so no closed seas defined.')
131            ENDIF
132         ELSE
133            IF( lwp ) THEN
134               WRITE(numout,*)
135               WRITE(numout,*) '   ==>>>   closea_mask field not found in domain_cfg file.'
136               WRITE(numout,*) '           No closed seas defined.'
137               WRITE(numout,*)
138               IF(lflush) CALL FLUSH(numout)
139            ENDIF
140            l_sbc_clo = .false.
141            jncs = 0 
142         ENDIF
143
144         l_clo_rnf = .false.
145
146         IF( l_sbc_clo ) THEN ! No point reading in closea_mask_rnf or closea_mask_empmr fields if no closed seas defined.
147
148            id = iom_varid(inum, 'closea_mask_rnf', ldstop = .false.)
149            IF( id > 0 ) THEN
150               l_clo_rnf = .true.           
151               ALLOCATE( closea_mask_rnf(jpi,jpj) , STAT=ierr )
152               IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'dom_clo: failed to allocate closea_mask_rnf array')
153               CALL iom_get ( inum, jpdom_data, 'closea_mask_rnf', zdata_in )
154               closea_mask_rnf(:,:) = NINT(zdata_in(:,:)) * tmask(:,:,1)
155               ! number of closed seas rnf mappings = global maximum in closea_mask_rnf field
156               jncsr = maxval(closea_mask_rnf(:,:))
157               CALL mpp_max('closea', jncsr)
158               IF( jncsr > 0 ) THEN
159                  IF( lwp ) THEN
160                     WRITE(numout,*) 'Number of closed seas rnf mappings : ',jncsr
161                     IF(lflush) CALL FLUSH(numout)
162                  ENDIF
163               ELSE
164                  CALL ctl_stop( 'Problem with closea_mask_rnf field in domain_cfg file. Has no values > 0 so no closed seas rnf mappings defined.')
165               ENDIF
166            ELSE
167               IF( lwp ) THEN
168                  WRITE(numout,*) 'closea_mask_rnf field not found in domain_cfg file. No closed seas rnf mappings defined.'
169                  IF(lflush) CALL FLUSH(numout)
170               ENDIF
171               jncsr = 0
172            ENDIF
173 
174            id = iom_varid(inum, 'closea_mask_empmr', ldstop = .false.)
175            IF( id > 0 ) THEN
176               l_clo_rnf = .true.           
177               ALLOCATE( closea_mask_empmr(jpi,jpj) , STAT=ierr )
178               IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'dom_clo: failed to allocate closea_mask_empmr array')
179               CALL iom_get ( inum, jpdom_data, 'closea_mask_empmr', zdata_in )
180               closea_mask_empmr(:,:) = NINT(zdata_in(:,:)) * tmask(:,:,1)
181               ! number of closed seas empmr mappings = global maximum value in closea_mask_empmr field
182               jncse = maxval(closea_mask_empmr(:,:))
183               CALL mpp_max('closea', jncse)
184               IF( jncse > 0 ) THEN
185                  IF( lwp ) THEN
186                     WRITE(numout,*) 'Number of closed seas empmr mappings : ',jncse
187                     IF(lflush) CALL FLUSH(numout)
188                  ENDIF
189               ELSE
190                  CALL ctl_stop( 'Problem with closea_mask_empmr field in domain_cfg file. Has no values > 0 so no closed seas empmr mappings defined.')
191               ENDIF
192            ELSE
193               IF( lwp ) THEN
194                  WRITE(numout,*) 'closea_mask_empmr field not found in domain_cfg file. No closed seas empmr mappings defined.'
195                  IF(lflush) CALL FLUSH(numout)
196               ENDIF
197               jncse = 0
198            ENDIF
199
200         ENDIF ! l_sbc_clo
201         !
202         CALL iom_close( inum )
203         !
204      ELSE ! ln_read_cfg = .false. so no domain_cfg file
205         IF( lwp ) THEN
206            WRITE(numout,*) 'No domain_cfg file so no closed seas defined.'
207            IF(lflush) CALL FLUSH(numout)
208         ENDIF
209         l_sbc_clo = .false.
210         l_clo_rnf = .false.
211      ENDIF
212      !
213   END SUBROUTINE dom_clo
214
215
216   SUBROUTINE sbc_clo( kt )
217      !!---------------------------------------------------------------------
218      !!                  ***  ROUTINE sbc_clo  ***
219      !!                   
220      !! ** Purpose :   Special handling of closed seas
221      !!
222      !! ** Method  :   Water flux is forced to zero over closed sea
223      !!      Excess is shared between remaining ocean, or
224      !!      put as run-off in open ocean.
225      !!
226      !! ** Action  :   emp updated surface freshwater fluxes and associated heat content at kt
227      !!----------------------------------------------------------------------
228      INTEGER         , INTENT(in   ) ::   kt       ! ocean model time step
229      !
230      INTEGER             ::   ierr
231      INTEGER             ::   jc, jcr, jce   ! dummy loop indices
232      REAL(wp), PARAMETER ::   rsmall = 1.e-20_wp    ! Closed sea correction epsilon
233      REAL(wp)            ::   zfwf_total, zcoef, zcoef1         !
234      REAL(wp), DIMENSION(jncs)    ::   zfwf      !:
235      REAL(wp), DIMENSION(jncsr+1) ::   zfwfr     !: freshwater fluxes over closed seas
236      REAL(wp), DIMENSION(jncse+1) ::   zfwfe     !:
237      REAL(wp), DIMENSION(jpi,jpj) ::   ztmp2d   ! 2D workspace
238      !!----------------------------------------------------------------------
239      !
240      IF( ln_timing )  CALL timing_start('sbc_clo')
241      !
242      !                                                   !------------------!
243      IF( kt == nit000 ) THEN                             !  Initialisation  !
244         !                                                !------------------!
245         IF(lwp) THEN
246            WRITE(numout,*)
247            WRITE(numout,*)'sbc_clo : closed seas '
248            WRITE(numout,*)'~~~~~~~'
249            IF(lflush) CALL FLUSH(numout)
250         ENDIF
251
252         ALLOCATE( surf(jncs+1) , STAT=ierr )
253         IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'sbc_clo: failed to allocate surf array')
254         surf(:) = 0.e0_wp
255         !
256         ! jncsr can be zero so add 1 to avoid allocating zero-length array
257         ALLOCATE( surfr(jncsr+1) , STAT=ierr )
258         IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'sbc_clo: failed to allocate surfr array')
259         surfr(:) = 0.e0_wp
260         !
261         ! jncse can be zero so add 1 to avoid allocating zero-length array
262         ALLOCATE( surfe(jncse+1) , STAT=ierr )
263         IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'sbc_clo: failed to allocate surfe array')
264         surfe(:) = 0.e0_wp
265         !
266         surf(jncs+1) = glob_sum( 'closea', e1e2t(:,:) )   ! surface of the global ocean
267         !
268         !                                        ! surface areas of closed seas
269         DO jc = 1, jncs
270            ztmp2d(:,:) = 0.e0_wp
271            WHERE( closea_mask(:,:) == jc ) ztmp2d(:,:) = e1e2t(:,:) * tmask_i(:,:)
272            surf(jc) = glob_sum( 'closea', ztmp2d(:,:) )
273         END DO
274         !
275         ! jncs+1 : surface area of global ocean, closed seas excluded
276         surf(jncs+1) = surf(jncs+1) - SUM(surf(1:jncs))
277         !
278         !                                        ! surface areas of rnf target areas
279         IF( jncsr > 0 ) THEN
280            DO jcr = 1, jncsr
281               ztmp2d(:,:) = 0.e0_wp
282               WHERE( closea_mask_rnf(:,:) == jcr .and. closea_mask(:,:) == 0 ) ztmp2d(:,:) = e1e2t(:,:) * tmask_i(:,:)
283               surfr(jcr) = glob_sum( 'closea', ztmp2d(:,:) )
284            END DO
285         ENDIF
286         !
287         !                                        ! surface areas of empmr target areas
288         IF( jncse > 0 ) THEN
289            DO jce = 1, jncse
290               ztmp2d(:,:) = 0.e0_wp
291               WHERE( closea_mask_empmr(:,:) == jce .and. closea_mask(:,:) == 0 ) ztmp2d(:,:) = e1e2t(:,:) * tmask_i(:,:)
292               surfe(jce) = glob_sum( 'closea', ztmp2d(:,:) )
293            END DO
294         ENDIF
295         !
296         IF(lwp) THEN
297            WRITE(numout,*)'     Closed sea surface areas (km2)'
298            DO jc = 1, jncs
299               WRITE(numout,FMT='(1I3,5X,ES12.2)') jc, surf(jc) * 1.0e-6
300            END DO
301            WRITE(numout,FMT='(A,ES12.2)') 'Global surface area excluding closed seas (km2): ', surf(jncs+1) * 1.0e-6
302         !
303            IF(jncsr > 0) THEN
304               WRITE(numout,*)'     Closed sea target rnf surface areas (km2)'
305               DO jcr = 1, jncsr
306                  WRITE(numout,FMT='(1I3,5X,ES12.2)') jcr, surfr(jcr) * 1.0e-6
307               END DO
308            ENDIF
309         !
310            IF(jncse > 0) THEN
311               WRITE(numout,*)'     Closed sea target empmr surface areas (km2)'
312               DO jce = 1, jncse
313                  WRITE(numout,FMT='(1I3,5X,ES12.2)') jce, surfe(jce) * 1.0e-6
314               END DO
315            ENDIF
316            IF(lflush) CALL FLUSH(numout)
317         ENDIF
318      ENDIF
319      !
320      !                                                      !--------------------!
321      !                                                      !  update emp        !
322      !                                                      !--------------------!
323
324      zfwf_total = 0._wp
325
326      !
327      ! 1. Work out total freshwater fluxes over closed seas from EMP - RNF.
328      !
329      zfwf(:) = 0.e0_wp           
330      DO jc = 1, jncs
331         ztmp2d(:,:) = 0.e0_wp
332         WHERE( closea_mask(:,:) == jc ) ztmp2d(:,:) = e1e2t(:,:) * ( emp(:,:)-rnf(:,:) ) * tmask_i(:,:)
333         zfwf(jc) = glob_sum( 'closea', ztmp2d(:,:) )
334      END DO
335      zfwf_total = SUM(zfwf)
336
337      zfwfr(:) = 0.e0_wp           
338      IF( jncsr > 0 ) THEN
339         !
340         ! 2. Work out total FW fluxes over rnf source areas and add to rnf target areas.
341         !    Where zfwf is negative add flux at specified runoff points and subtract from fluxes for global redistribution.
342         !    Where positive leave in global redistribution total.
343         !
344         DO jcr = 1, jncsr
345            !
346            ztmp2d(:,:) = 0.e0_wp
347            WHERE( closea_mask_rnf(:,:) == jcr .and. closea_mask(:,:) > 0 ) ztmp2d(:,:) = e1e2t(:,:) * ( emp(:,:)-rnf(:,:) ) * tmask_i(:,:)
348            zfwfr(jcr) = glob_sum( 'closea', ztmp2d(:,:) )
349            !
350            ! The following if avoids the redistribution of the round off
351            IF ( ABS(zfwfr(jcr) / surf(jncs+1) ) > rsmall) THEN
352               !
353               ! Add residuals to target runoff points if negative and subtract from total to be added globally
354               IF( zfwfr(jcr) < 0.0 ) THEN
355                  zfwf_total = zfwf_total - zfwfr(jcr)
356                  zcoef    = zfwfr(jcr) / surfr(jcr)
357                  zcoef1   = rcp * zcoef
358                  WHERE( closea_mask_rnf(:,:) == jcr .and. closea_mask(:,:) == 0.0)
359                     emp(:,:) = emp(:,:) + zcoef
360                     qns(:,:) = qns(:,:) - zcoef1 * sst_m(:,:)
361                  ENDWHERE
362               ENDIF
363               !
364            ENDIF
365         END DO
366      ENDIF  ! jncsr > 0   
367      !
368      zfwfe(:) = 0.e0_wp           
369      IF( jncse > 0 ) THEN
370         !
371         ! 3. Work out total fluxes over empmr source areas and add to empmr target areas.
372         !
373         DO jce = 1, jncse
374            !
375            ztmp2d(:,:) = 0.e0_wp
376            WHERE( closea_mask_empmr(:,:) == jce .and. closea_mask(:,:) > 0 ) ztmp2d(:,:) = e1e2t(:,:) * ( emp(:,:)-rnf(:,:) ) * tmask_i(:,:)
377            zfwfe(jce) = glob_sum( 'closea', ztmp2d(:,:) )
378            !
379            ! The following if avoids the redistribution of the round off
380            IF ( ABS( zfwfe(jce) / surf(jncs+1) ) > rsmall ) THEN
381               !
382               ! Add residuals to runoff points and subtract from total to be added globally
383               zfwf_total = zfwf_total - zfwfe(jce)
384               zcoef    = zfwfe(jce) / surfe(jce)
385               zcoef1   = rcp * zcoef
386               WHERE( closea_mask_empmr(:,:) == jce .and. closea_mask(:,:) == 0.0)
387                  emp(:,:) = emp(:,:) + zcoef
388                  qns(:,:) = qns(:,:) - zcoef1 * sst_m(:,:)
389               ENDWHERE
390               !
391            ENDIF
392         END DO
393      ENDIF ! jncse > 0   
394
395      !
396      ! 4. Spread residual flux over global ocean.
397      !
398      ! The following if avoids the redistribution of the round off
399      IF ( ABS(zfwf_total / surf(jncs+1) ) > rsmall) THEN
400         zcoef    = zfwf_total / surf(jncs+1)
401         zcoef1   = rcp * zcoef
402         WHERE( closea_mask(:,:) == 0 )
403            emp(:,:) = emp(:,:) + zcoef
404            qns(:,:) = qns(:,:) - zcoef1 * sst_m(:,:)
405         ENDWHERE
406      ENDIF
407
408      !
409      ! 5. Subtract area means from emp (and qns) over closed seas to give zero mean FW flux over each sea.
410      !
411      DO jc = 1, jncs
412         ! The following if avoids the redistribution of the round off
413         IF ( ABS(zfwf(jc) / surf(jncs+1) ) > rsmall) THEN
414            !
415            ! Subtract residuals from fluxes over closed sea
416            zcoef    = zfwf(jc) / surf(jc)
417            zcoef1   = rcp * zcoef
418            WHERE( closea_mask(:,:) == jc )
419               emp(:,:) = emp(:,:) - zcoef
420               qns(:,:) = qns(:,:) + zcoef1 * sst_m(:,:)
421            ENDWHERE
422            !
423         ENDIF
424      END DO
425      !
426      emp (:,:) = emp (:,:) * tmask(:,:,1)
427      !
428      CALL lbc_lnk( 'closea', emp , 'T', 1._wp )
429      !
430   END SUBROUTINE sbc_clo
431
432   SUBROUTINE clo_rnf( p_rnfmsk )
433      !!---------------------------------------------------------------------
434      !!                  ***  ROUTINE sbc_rnf  ***
435      !!                   
436      !! ** Purpose :   allow the treatment of closed sea outflow grid-points
437      !!                to be the same as river mouth grid-points
438      !!
439      !! ** Method  :   set to 1 the runoff mask (mskrnf, see sbcrnf module)
440      !!                at the closed sea outflow grid-point.
441      !!
442      !! ** Action  :   update (p_)mskrnf (set 1 at closed sea outflow)
443      !!----------------------------------------------------------------------
444      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) ::   p_rnfmsk   ! river runoff mask (rnfmsk array)
445      !!----------------------------------------------------------------------
446      !
447      IF( jncsr > 0 ) THEN
448         WHERE( closea_mask_rnf(:,:) > 0 .and. closea_mask(:,:) == 0 )
449            p_rnfmsk(:,:) = MAX( p_rnfmsk(:,:), 1.0_wp )
450         ENDWHERE
451      ENDIF
452      !
453      IF( jncse > 0 ) THEN
454         WHERE( closea_mask_empmr(:,:) > 0 .and. closea_mask(:,:) == 0 )
455            p_rnfmsk(:,:) = MAX( p_rnfmsk(:,:), 1.0_wp )
456         ENDWHERE
457      ENDIF
458      !
459   END SUBROUTINE clo_rnf
460   
461     
462   SUBROUTINE clo_bat( k_top, k_bot )
463      !!---------------------------------------------------------------------
464      !!                  ***  ROUTINE clo_bat  ***
465      !!                   
466      !! ** Purpose :   Suppress closed sea from the domain
467      !!
468      !! ** Method  :   Read in closea_mask field (if it exists) from domain_cfg file.
469      !!                Where closea_mask > 0 set first and last ocean level to 0
470      !!                (As currently coded you can't define a closea_mask field in
471      !!                usr_def_zgr).
472      !!
473      !! ** Action  :   set k_top=0 and k_bot=0 over closed seas
474      !!----------------------------------------------------------------------
475      INTEGER, DIMENSION(:,:), INTENT(inout) ::   k_top, k_bot   ! ocean first and last level indices
476      INTEGER                           :: inum, id
477      INTEGER,  DIMENSION(jpi,jpj) :: closea_mask ! closea_mask field
478      REAL(wp), DIMENSION(jpi,jpj) :: zdata_in ! temporary real array for input
479      !!----------------------------------------------------------------------
480      !
481      IF(lwp) THEN                     ! Control print
482         WRITE(numout,*)
483         WRITE(numout,*) 'clo_bat : suppression of closed seas'
484         WRITE(numout,*) '~~~~~~~'
485         IF(lflush) CALL FLUSH(numout)
486      ENDIF
487      !
488      IF( ln_read_cfg ) THEN
489         !
490         CALL iom_open( cn_domcfg, inum )
491         !
492         id = iom_varid(inum, 'closea_mask', ldstop = .false.)     
493         IF( id > 0 ) THEN
494            IF( lwp ) THEN
495               WRITE(numout,*) 'Suppressing closed seas in bathymetry based on closea_mask field,'
496               IF(lflush) CALL FLUSH(numout)
497            ENDIF
498            CALL iom_get ( inum, jpdom_data, 'closea_mask', zdata_in )
499            closea_mask(:,:) = NINT(zdata_in(:,:))
500            WHERE( closea_mask(:,:) > 0 )
501               k_top(:,:) = 0   
502               k_bot(:,:) = 0   
503            ENDWHERE
504         ELSE
505            IF( lwp ) THEN
506               WRITE(numout,*) 'No closea_mask field found in domain_cfg file. No suppression of closed seas.'
507               IF(lflush) CALL FLUSH(numout)
508            ENDIF
509         ENDIF
510         !
511         CALL iom_close(inum)
512         !
513      ELSE
514         IF( lwp ) THEN
515            WRITE(numout,*) 'No domain_cfg file => no suppression of closed seas.'
516            IF(lflush) CALL FLUSH(numout)
517         ENDIF
518      ENDIF
519      !
520      ! Initialise l_sbc_clo and l_clo_rnf for this case (ln_closea=.false.)
521      l_sbc_clo = .false.
522      l_clo_rnf = .false.
523      !
524   END SUBROUTINE clo_bat
525
526   !!======================================================================
527END MODULE closea
528
Note: See TracBrowser for help on using the repository browser.