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-02_ISF_domcfg/src – NEMO

source: NEMO/branches/2019/ENHANCE-02_ISF_domcfg/src/domain.F90 @ 12166

Last change on this file since 12166 was 11986, checked in by mathiot, 4 years ago

ENHANCE-02_ISF_domcfg: changes needed after Dave's review

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