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 utils/tools_dev_r12970_AGRIF_CMEMS/DOMAINcfg/src – NEMO

source: utils/tools_dev_r12970_AGRIF_CMEMS/DOMAINcfg/src/domain.F90 @ 13056

Last change on this file since 13056 was 13056, checked in by rblod, 4 years ago

ticket #2129 : cleaning domcfg

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