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.
domain.F90 in NEMO/branches/2019/ENHANCE-03_domcfg/src – NEMO

source: NEMO/branches/2019/ENHANCE-03_domcfg/src/domain.F90 @ 11604

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

ENHANCE-03_domcfg: remove useless variable in domclo and domutil + cosmetics changes (ticket #2143)

File size: 22.7 KB
Line 
1MODULE domain
2   !!==============================================================================
3   !!                       ***  MODULE domain   ***
4   !! Ocean initialization : domain initialization
5   !!==============================================================================
6   !! History :  OPA  !  1990-10  (C. Levy - G. Madec)  Original code
7   !!                 !  1992-01  (M. Imbard) insert time step initialization
8   !!                 !  1996-06  (G. Madec) generalized vertical coordinate
9   !!                 !  1997-02  (G. Madec) creation of domwri.F
10   !!                 !  2001-05  (E.Durand - G. Madec) insert closed sea
11   !!   NEMO     1.0  !  2002-08  (G. Madec)  F90: Free form and module
12   !!            2.0  !  2005-11  (V. Garnier) Surface pressure gradient organization
13   !!            3.3  !  2010-11  (G. Madec)  initialisation in C1D configuration
14   !!            3.6  !  2013     ( J. Simeon, C. Calone, G. Madec, C. Ethe ) Online coarsening of outputs
15   !!            3.7  !  2015-11  (G. Madec, A. Coward)  time varying zgr by default
16   !!----------------------------------------------------------------------
17   
18   !!----------------------------------------------------------------------
19   !!   dom_init       : initialize the space and time domain
20   !!   dom_nam        : read and contral domain namelists
21   !!   dom_ctl        : control print for the ocean domain
22   !!----------------------------------------------------------------------
23   USE dom_oce         ! domain: ocean
24   USE phycst          ! physical constants
25   USE domhgr          ! domain: set the horizontal mesh
26   USE domzgr          ! domain: set the vertical mesh
27   USE dommsk          ! domain: set the mask system
28   USE domclo          ! domain: set closed sea mask
29   !
30   USE in_out_manager  ! I/O manager
31   USE iom             !
32
33   IMPLICIT NONE
34   PRIVATE
35
36   PUBLIC   dom_init   ! called by opa.F90
37   PUBLIC   dom_nam  ! called by opa.F90
38   PUBLIC   cfg_write   ! called by opa.F90
39
40   !!-------------------------------------------------------------------------
41   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
42   !! $Id: domain.F90 6140 2015-12-21 11:35:23Z timgraham $
43   !! Software governed by the CeCILL licence        (./LICENSE)
44   !!-------------------------------------------------------------------------
45CONTAINS
46
47   SUBROUTINE dom_init
48      !!----------------------------------------------------------------------
49      !!                  ***  ROUTINE dom_init  ***
50      !!                   
51      !! ** Purpose :   Domain initialization. Call the routines that are
52      !!              required to create the arrays which define the space
53      !!              and time domain of the ocean model.
54      !!
55      !! ** Method  : - dom_msk: compute the masks from the bathymetry file
56      !!              - dom_hgr: compute or read the horizontal grid-point position
57      !!                         and scale factors, and the coriolis factor
58      !!              - dom_zgr: define the vertical coordinate and the bathymetry
59      !!              - dom_stp: defined the model time step
60      !!              - dom_wri: create the meshmask file if nmsh=1
61      !!              - 1D configuration, move Coriolis, u and v at T-point
62      !!----------------------------------------------------------------------
63      !
64      IF(lwp) THEN
65         WRITE(numout,*)
66         WRITE(numout,*) 'dom_init : domain initialization'
67         WRITE(numout,*) '~~~~~~~~'
68      ENDIF
69      !
70      !                       !==  Reference coordinate system  ==!
71      !
72      CALL dom_nam                  ! read namelist ( namrun, namdom )
73      !
74      CALL dom_hgr                  ! Horizontal mesh
75      !
76      CALL dom_zgr                  ! Vertical mesh and bathymetry
77      !
78      IF ( ln_domclo .OR. nn_msh > 0 ) CALL dom_msk ! compute mask (needed by dom_clo)
79      !
80      IF ( ln_domclo ) CALL dom_clo ! Closed seas and lake
81      !
82      CALL cfg_write                ! create the configuration file
83      !
84   END SUBROUTINE dom_init
85
86   SUBROUTINE dom_nam
87      !!----------------------------------------------------------------------
88      !!                     ***  ROUTINE dom_nam  ***
89      !!                   
90      !! ** Purpose :   read domaine namelists and print the variables.
91      !!
92      !! ** input   : - namrun namelist
93      !!              - namdom namelist
94      !!              - namnc4 namelist   ! "key_netcdf4" only
95      !!----------------------------------------------------------------------
96      USE ioipsl
97      NAMELIST/namrun/ cn_ocerst_indir, cn_ocerst_outdir, nn_stocklist, ln_rst_list,                 &
98                       nn_no   , cn_exp   , cn_ocerst_in, cn_ocerst_out, ln_rstart , nn_rstctl ,     &
99         &             nn_it000, nn_itend , nn_date0    , nn_time0     , nn_leapy  , nn_istate ,     &
100         &             nn_stock, nn_write , ln_mskland  , ln_clobber   , nn_chunksz, nn_euler  ,     &
101         &             ln_cfmeta, ln_iscpl
102      NAMELIST/namdom/ nn_bathy, cn_topo, cn_bath, cn_lon, cn_lat, nn_interp,                        &
103         &             rn_bathy , rn_e3zps_min, rn_e3zps_rat, nn_msh, rn_hmin, rn_isfhmin,           &
104         &             rn_atfp , rn_rdt   , ln_crs      , jphgr_msh ,                  &
105         &             ppglam0, ppgphi0, ppe1_deg, ppe2_deg, ppe1_m, ppe2_m,                         &
106         &             ppsur, ppa0, ppa1, ppkth, ppacr, ppdzmin, pphmax, ldbletanh,                  &
107         &             ppa2, ppkth2, ppacr2
108
109
110
111      INTEGER  ::   ios                 ! Local integer output status for namelist read
112      !!----------------------------------------------------------------------
113
114      REWIND( numnam_ref )              ! Namelist namrun in reference namelist : Parameters of the run
115      READ  ( numnam_ref, namrun, IOSTAT = ios, ERR = 901)
116901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namrun in reference namelist', lwp )
117
118      REWIND( numnam_cfg )              ! Namelist namrun in configuration namelist : Parameters of the run
119      READ  ( numnam_cfg, namrun, IOSTAT = ios, ERR = 902 )
120902   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namrun in configuration namelist', lwp )
121      IF(lwm) WRITE ( numond, namrun )
122      !
123      IF(lwp) THEN                  ! control print
124         WRITE(numout,*)
125         WRITE(numout,*) 'dom_nam  : domain initialization through namelist read'
126         WRITE(numout,*) '~~~~~~~ '
127         WRITE(numout,*) '   Namelist namrun'
128         WRITE(numout,*) '      experiment name for output      cn_exp     = ', cn_exp
129         WRITE(numout,*) '      mask land points                ln_mskland = ', ln_mskland
130         WRITE(numout,*) '      additional CF standard metadata ln_cfmeta  = ', ln_cfmeta
131         WRITE(numout,*) '      overwrite an existing file      ln_clobber = ', ln_clobber
132         WRITE(numout,*) '      NetCDF chunksize (bytes)        nn_chunksz = ', nn_chunksz
133      ENDIF
134
135      cexper = cn_exp
136      nrstdt = nn_rstctl
137      nit000 = nn_it000
138      nitend = nn_itend
139      ndate0 = nn_date0
140      nleapy = nn_leapy
141      ninist = nn_istate
142      nstock = nn_stock
143      nstocklist = nn_stocklist
144      nwrite = nn_write
145      neuler = nn_euler
146      IF ( neuler == 1 .AND. .NOT. ln_rstart ) THEN
147         WRITE(ctmp1,*) 'ln_rstart =.FALSE., nn_euler is forced to 0 '
148         CALL ctl_warn( ctmp1 )
149         neuler = 0
150      ENDIF
151
152      !                             ! control of output frequency
153      IF ( nstock == 0 .OR. nstock > nitend ) THEN
154         WRITE(ctmp1,*) 'nstock = ', nstock, ' it is forced to ', nitend
155         CALL ctl_warn( ctmp1 )
156         nstock = nitend
157      ENDIF
158      IF ( nwrite == 0 ) THEN
159         WRITE(ctmp1,*) 'nwrite = ', nwrite, ' it is forced to ', nitend
160         CALL ctl_warn( ctmp1 )
161         nwrite = nitend
162      ENDIF
163
164
165
166
167      SELECT CASE ( nleapy )        ! Choose calendar for IOIPSL
168      CASE (  1 ) 
169         CALL ioconf_calendar('gregorian')
170         IF(lwp) WRITE(numout,*) '   The IOIPSL calendar is "gregorian", i.e. leap year'
171      CASE (  0 )
172         CALL ioconf_calendar('noleap')
173         IF(lwp) WRITE(numout,*) '   The IOIPSL calendar is "noleap", i.e. no leap year'
174      CASE ( 30 )
175         CALL ioconf_calendar('360d')
176         IF(lwp) WRITE(numout,*) '   The IOIPSL calendar is "360d", i.e. 360 days in a year'
177      END SELECT
178
179
180
181
182      REWIND( numnam_ref )              ! Namelist namdom in reference namelist : space & time domain (bathymetry, mesh, timestep)
183      READ  ( numnam_ref, namdom, IOSTAT = ios, ERR = 903)
184903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdom in reference namelist', lwp )
185 
186      !
187      REWIND( numnam_cfg )              ! Namelist namdom in configuration namelist : space & time domain (bathymetry, mesh, timestep)
188      READ  ( numnam_cfg, namdom, IOSTAT = ios, ERR = 904 )
189904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdom in configuration namelist', lwp )
190      IF(lwm) WRITE ( numond, namdom )
191      !
192      IF(lwp) THEN
193         WRITE(numout,*)
194         WRITE(numout,*) '   Namelist namdom : space & time domain'
195         WRITE(numout,*) '      flag read/compute bathymetry      nn_bathy     = ', nn_bathy
196         IF( nn_bathy == 2 ) THEN
197            WRITE(numout,*) '      compute bathymetry from file      cn_topo      = ', cn_topo
198         ENDIF   
199         WRITE(numout,*) '      Depth (if =0 bathy=jpkm1)         rn_bathy     = ', rn_bathy
200         WRITE(numout,*) '      min depth of the ocean    (>0) or    rn_hmin   = ', rn_hmin
201         WRITE(numout,*) '      min number of ocean level (<0)       '
202         WRITE(numout,*) '      treshold to open the isf cavity   rn_isfhmin   = ', rn_isfhmin, ' (m)'
203         WRITE(numout,*) '      minimum thickness of partial      rn_e3zps_min = ', rn_e3zps_min, ' (m)'
204         WRITE(numout,*) '         step level                     rn_e3zps_rat = ', rn_e3zps_rat
205         WRITE(numout,*) '      create mesh/mask file(s)          nn_msh       = ', nn_msh
206         WRITE(numout,*) '           = 0   no file created           '
207         WRITE(numout,*) '           = 1   mesh_mask                 '
208         WRITE(numout,*) '           = 2   mesh and mask             '
209         WRITE(numout,*) '           = 3   mesh_hgr, msh_zgr and mask'
210         WRITE(numout,*) '      type of horizontal mesh jphgr_msh           = ', jphgr_msh
211         WRITE(numout,*) '      longitude of first raw and column T-point ppglam0 = ', ppglam0
212         WRITE(numout,*) '      latitude  of first raw and column T-point ppgphi0 = ', ppgphi0
213         WRITE(numout,*) '      zonal      grid-spacing (degrees) ppe1_deg        = ', ppe1_deg
214         WRITE(numout,*) '      meridional grid-spacing (degrees) ppe2_deg        = ', ppe2_deg
215         WRITE(numout,*) '      zonal      grid-spacing (degrees) ppe1_m          = ', ppe1_m
216         WRITE(numout,*) '      meridional grid-spacing (degrees) ppe2_m          = ', ppe2_m
217         WRITE(numout,*) '      ORCA r4, r2 and r05 coefficients  ppsur           = ', ppsur
218         WRITE(numout,*) '                                        ppa0            = ', ppa0
219         WRITE(numout,*) '                                        ppa1            = ', ppa1
220         WRITE(numout,*) '                                        ppkth           = ', ppkth
221         WRITE(numout,*) '                                        ppacr           = ', ppacr
222         WRITE(numout,*) '      Minimum vertical spacing ppdzmin                  = ', ppdzmin
223         WRITE(numout,*) '      Maximum depth pphmax                              = ', pphmax
224         WRITE(numout,*) '      Use double tanf function for vertical coordinates ldbletanh = ', ldbletanh
225         WRITE(numout,*) '      Double tanh function parameters ppa2              = ', ppa2
226         WRITE(numout,*) '                                      ppkth2            = ', ppkth2
227         WRITE(numout,*) '                                      ppacr2            = ', ppacr2
228      ENDIF
229      !
230      ntopo     = nn_bathy          ! conversion DOCTOR names into model names (this should disappear soon)
231      e3zps_min = rn_e3zps_min
232      e3zps_rat = rn_e3zps_rat
233      nmsh      = nn_msh
234      atfp      = rn_atfp
235      rdt       = rn_rdt
236
237      snc4set%luse = .FALSE.        ! No NetCDF 4 case
238      !
239   END SUBROUTINE dom_nam
240
241
242   SUBROUTINE dom_ctl
243      !!----------------------------------------------------------------------
244      !!                     ***  ROUTINE dom_ctl  ***
245      !!
246      !! ** Purpose :   Domain control.
247      !!
248      !! ** Method  :   compute and print extrema of masked scale factors
249      !!----------------------------------------------------------------------
250      INTEGER ::   iimi1, ijmi1, iimi2, ijmi2, iima1, ijma1, iima2, ijma2
251      INTEGER, DIMENSION(2) ::   iloc   !
252      REAL(wp) ::   ze1min, ze1max, ze2min, ze2max
253      !!----------------------------------------------------------------------
254      !
255#undef CHECK_DOM
256#ifdef CHECK_DOM
257      IF(lk_mpp) THEN
258         CALL mpp_minloc( e1t(:,:), tmask_i(:,:), ze1min, iimi1,ijmi1 )
259         CALL mpp_minloc( e2t(:,:), tmask_i(:,:), ze2min, iimi2,ijmi2 )
260         CALL mpp_maxloc( e1t(:,:), tmask_i(:,:), ze1max, iima1,ijma1 )
261         CALL mpp_maxloc( e2t(:,:), tmask_i(:,:), ze2max, iima2,ijma2 )
262      ELSE
263         ze1min = MINVAL( e1t(:,:), mask = tmask_i(:,:) == 1._wp )   
264         ze2min = MINVAL( e2t(:,:), mask = tmask_i(:,:) == 1._wp )   
265         ze1max = MAXVAL( e1t(:,:), mask = tmask_i(:,:) == 1._wp )   
266         ze2max = MAXVAL( e2t(:,:), mask = tmask_i(:,:) == 1._wp )   
267
268         iloc  = MINLOC( e1t(:,:), mask = tmask_i(:,:) == 1._wp )
269         iimi1 = iloc(1) + nimpp - 1
270         ijmi1 = iloc(2) + njmpp - 1
271         iloc  = MINLOC( e2t(:,:), mask = tmask_i(:,:) == 1._wp )
272         iimi2 = iloc(1) + nimpp - 1
273         ijmi2 = iloc(2) + njmpp - 1
274         iloc  = MAXLOC( e1t(:,:), mask = tmask_i(:,:) == 1._wp )
275         iima1 = iloc(1) + nimpp - 1
276         ijma1 = iloc(2) + njmpp - 1
277         iloc  = MAXLOC( e2t(:,:), mask = tmask_i(:,:) == 1._wp )
278         iima2 = iloc(1) + nimpp - 1
279         ijma2 = iloc(2) + njmpp - 1
280      ENDIF
281      IF(lwp) THEN
282         WRITE(numout,*)
283         WRITE(numout,*) 'dom_ctl : extrema of the masked scale factors'
284         WRITE(numout,*) '~~~~~~~'
285         WRITE(numout,"(14x,'e1t maxi: ',1f10.2,' at i = ',i5,' j= ',i5)") ze1max, iima1, ijma1
286         WRITE(numout,"(14x,'e1t mini: ',1f10.2,' at i = ',i5,' j= ',i5)") ze1min, iimi1, ijmi1
287         WRITE(numout,"(14x,'e2t maxi: ',1f10.2,' at i = ',i5,' j= ',i5)") ze2max, iima2, ijma2
288         WRITE(numout,"(14x,'e2t mini: ',1f10.2,' at i = ',i5,' j= ',i5)") ze2min, iimi2, ijmi2
289      ENDIF
290#endif
291      !
292   END SUBROUTINE dom_ctl
293
294
295   SUBROUTINE cfg_write
296      !!----------------------------------------------------------------------
297      !!                  ***  ROUTINE cfg_write  ***
298      !!                   
299      !! ** Purpose :   Create the "domain_cfg" file, a NetCDF file which
300      !!              contains all the ocean domain informations required to
301      !!              define an ocean configuration.
302      !!
303      !! ** Method  :   Write in a file all the arrays required to set up an
304      !!              ocean configuration.
305      !!
306      !! ** output file :   domain_cfg.nc : domain size, characteristics,horizontal mesh,
307      !!                              Coriolis parameter, and vertical scale factors
308      !!                              NB: also contains ORCA family information (if cp_cfg = "ORCA")
309      !!                              and depths (ln_e3_dep=F)
310      !!----------------------------------------------------------------------
311      INTEGER           ::   ji, jj, jk   ! dummy loop indices
312      INTEGER           ::   izco, izps, isco, icav
313      INTEGER           ::   inum     ! temprary units for 'domain_cfg.nc' file
314      CHARACTER(len=21) ::   clnam    ! filename (mesh and mask informations)
315      REAL(wp), DIMENSION(jpi,jpj) ::   z2d   ! workspace
316      !!----------------------------------------------------------------------
317      !
318      IF(lwp) WRITE(numout,*)
319      IF(lwp) WRITE(numout,*) 'cfg_write : create the "domain_cfg.nc" file containing all required configuration information'
320      IF(lwp) WRITE(numout,*) '~~~~~~~~~'
321      !
322      !                       ! ============================= !
323      !                       !  create 'domain_cfg.nc' file  !
324      !                       ! ============================= !
325      !         
326      clnam = 'domain_cfg'  ! filename (configuration information)
327      CALL iom_open( TRIM(clnam), inum, ldwrt = .TRUE.)!, kiolib = jprstlib )
328     
329      !
330      !                             !==  ORCA family specificities  ==!
331      IF( cp_cfg == "ORCA" ) THEN
332         CALL iom_rstput( 0, 0, inum, 'ORCA'      , 1._wp            , ktype = jp_i4 )
333         CALL iom_rstput( 0, 0, inum, 'ORCA_index', REAL( jp_cfg, wp), ktype = jp_i4 )         
334      ENDIF
335      !                             !==  global domain size  ==!
336      !
337      CALL iom_rstput( 0, 0, inum, 'jpiglo', REAL( jpiglo, wp), ktype = jp_i4 )
338      CALL iom_rstput( 0, 0, inum, 'jpjglo', REAL( jpjglo, wp), ktype = jp_i4 )
339      CALL iom_rstput( 0, 0, inum, 'jpkglo', REAL( jpk   , wp), ktype = jp_i4 )
340      !
341      !                             !==  domain characteristics  ==!
342      !
343      !                                   ! lateral boundary of the global
344      !                                   domain
345      CALL iom_rstput( 0, 0, inum, 'jperio', REAL( jperio, wp), ktype = jp_i4 )
346      !
347      !                                   ! type of vertical coordinate
348      IF( ln_zco    ) THEN   ;   izco = 1   ;   ELSE   ;   izco = 0   ;   ENDIF
349      IF( ln_zps    ) THEN   ;   izps = 1   ;   ELSE   ;   izps = 0   ;   ENDIF
350      IF( ln_sco    ) THEN   ;   isco = 1   ;   ELSE   ;   isco = 0   ;   ENDIF
351      CALL iom_rstput( 0, 0, inum, 'ln_zco'   , REAL( izco, wp), ktype = jp_i4 )
352      CALL iom_rstput( 0, 0, inum, 'ln_zps'   , REAL( izps, wp), ktype = jp_i4 )
353      CALL iom_rstput( 0, 0, inum, 'ln_sco'   , REAL( isco, wp), ktype = jp_i4 )
354      !
355      !                                   ! ocean cavities under iceshelves
356      IF( ln_isfcav ) THEN   ;   icav = 1   ;   ELSE   ;   icav = 0   ;   ENDIF
357      CALL iom_rstput( 0, 0, inum, 'ln_isfcav', REAL( icav, wp), ktype = jp_i4 )
358      !
359      !                             !==  horizontal mesh  !
360      !
361      CALL iom_rstput( 0, 0, inum, 'glamt', glamt, ktype = jp_r8 )   ! latitude
362      CALL iom_rstput( 0, 0, inum, 'glamu', glamu, ktype = jp_r8 )
363      CALL iom_rstput( 0, 0, inum, 'glamv', glamv, ktype = jp_r8 )
364      CALL iom_rstput( 0, 0, inum, 'glamf', glamf, ktype = jp_r8 )
365      !                               
366      CALL iom_rstput( 0, 0, inum, 'gphit', gphit, ktype = jp_r8 )   ! longitude
367      CALL iom_rstput( 0, 0, inum, 'gphiu', gphiu, ktype = jp_r8 )
368      CALL iom_rstput( 0, 0, inum, 'gphiv', gphiv, ktype = jp_r8 )
369      CALL iom_rstput( 0, 0, inum, 'gphif', gphif, ktype = jp_r8 )
370      !                               
371      CALL iom_rstput( 0, 0, inum, 'e1t'  , e1t  , ktype = jp_r8 )   ! i-scale factors (e1.)
372      CALL iom_rstput( 0, 0, inum, 'e1u'  , e1u  , ktype = jp_r8 )
373      CALL iom_rstput( 0, 0, inum, 'e1v'  , e1v  , ktype = jp_r8 )
374      CALL iom_rstput( 0, 0, inum, 'e1f'  , e1f  , ktype = jp_r8 )
375      !
376      CALL iom_rstput( 0, 0, inum, 'e2t'  , e2t  , ktype = jp_r8 )   ! j-scale factors (e2.)
377      CALL iom_rstput( 0, 0, inum, 'e2u'  , e2u  , ktype = jp_r8 )
378      CALL iom_rstput( 0, 0, inum, 'e2v'  , e2v  , ktype = jp_r8 )
379      CALL iom_rstput( 0, 0, inum, 'e2f'  , e2f  , ktype = jp_r8 )
380      !
381      CALL iom_rstput( 0, 0, inum, 'ff_f' , ff_f , ktype = jp_r8 )   ! coriolis factor
382      CALL iom_rstput( 0, 0, inum, 'ff_t' , ff_t , ktype = jp_r8 )
383      !
384      !                             !==  vertical mesh  ==!
385      !                                                     
386      CALL iom_rstput( 0, 0, inum, 'e3t_1d'  , e3t_1d  , ktype = jp_r8 )   !  reference 1D-coordinate
387      CALL iom_rstput( 0, 0, inum, 'e3w_1d'  , e3w_1d  , ktype = jp_r8 )
388      !
389      CALL iom_rstput( 0, 0, inum, 'e3t_0'   , e3t_0   , ktype = jp_r8 )   !  vertical scale factors (e
390      CALL iom_rstput( 0, 0, inum, 'e3u_0'   , e3u_0   , ktype = jp_r8 )
391      CALL iom_rstput( 0, 0, inum, 'e3v_0'   , e3v_0   , ktype = jp_r8 )
392      CALL iom_rstput( 0, 0, inum, 'e3f_0'   , e3f_0   , ktype = jp_r8 )
393      CALL iom_rstput( 0, 0, inum, 'e3w_0'   , e3w_0   , ktype = jp_r8 )
394      CALL iom_rstput( 0, 0, inum, 'e3uw_0'  , e3uw_0  , ktype = jp_r8 )
395      CALL iom_rstput( 0, 0, inum, 'e3vw_0'  , e3vw_0  , ktype = jp_r8 )
396      !
397      IF(.NOT.ln_e3_dep ) THEN                                             !  depth (t- & w-points)
398         CALL iom_rstput( 0, 0, inum, 'gdept_1d', gdept_1d, ktype = jp_r8 )   ! required only with 
399         CALL iom_rstput( 0, 0, inum, 'gdepw_1d', gdepw_1d, ktype = jp_r8 )   ! the old e3. definition
400         CALL iom_rstput( 0, 0, inum, 'gdept_0' , gdept_0 , ktype = jp_r8 )
401         CALL iom_rstput( 0, 0, inum, 'gdepw_0' , gdepw_0 , ktype = jp_r8 )
402      ENDIF
403      !                                         
404      !                             !==  ocean top and bottom level  ==!
405      !
406      CALL iom_rstput( 0, 0, inum, 'bottom_level' , REAL( mbkt, wp )*ssmask , ktype = jp_i4 )   ! nb of ocean T-points
407      CALL iom_rstput( 0, 0, inum, 'top_level'    , REAL( mikt, wp )*ssmask , ktype = jp_i4 )   ! nb of ocean T-points (ISF)
408      DO jj = 1,jpj
409         DO ji = 1,jpi
410            z2d (ji,jj) = SUM ( e3t_0(ji,jj, 1:mbkt(ji,jj) ) ) * ssmask(ji,jj) 
411         END DO
412      END DO
413      CALL iom_rstput( 0, 0, inum, 'bathy_metry'   , z2d , ktype = jp_r4 )
414      !
415      !                              !== closed sea ==!
416      IF (ln_domclo) THEN
417         ! mask for the open sea
418         CALL iom_rstput( 0, 0, inum, 'mask_opensea' , msk_opnsea, ktype = jp_i4 )
419         ! mask for all the under closed sea
420         CALL iom_rstput( 0, 0, inum, 'mask_csundef' , msk_closea, ktype = jp_i4 )
421         ! mask for global, local net precip, local net precip and evaporation correction
422         CALL iom_rstput( 0, 0, inum, 'mask_csglo'   , msk_glo   , ktype = jp_i4 )
423         CALL iom_rstput( 0, 0, inum, 'mask_csemp'   , msk_emp   , ktype = jp_i4 )
424         CALL iom_rstput( 0, 0, inum, 'mask_csrnf'   , msk_rnf   , ktype = jp_i4 )
425         ! mask for the various river mouth (in case multiple lake in the same outlet)
426         CALL iom_rstput( 0, 0, inum, 'mask_csgrpglo', msk_gloid , ktype = jp_i4 )
427         CALL iom_rstput( 0, 0, inum, 'mask_csgrpemp', msk_empid , ktype = jp_i4 )
428         CALL iom_rstput( 0, 0, inum, 'mask_csgrprnf', msk_rnfid , ktype = jp_i4 )
429      END IF
430      !
431      !                                ! ============================
432      !                                !        close the files
433      !                                ! ============================
434      CALL iom_close( inum )
435      !
436   END SUBROUTINE cfg_write
437
438
439
440   !!======================================================================
441END MODULE domain
Note: See TracBrowser for help on using the repository browser.