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 @ 11129

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

simplification of domcfg (rm all var_n and var_b as it is not needed) (ticket #2143)

File size: 24.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 closea          ! closed seas
26   USE domhgr          ! domain: set the horizontal mesh
27   USE domzgr          ! domain: set the vertical mesh
28   USE dommsk          ! domain: set the mask system
29   USE domwri          ! domain: write the meshmask file
30   !
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_clo               ! Closed seas and lake
80      !
81      CALL dom_hgr               ! Horizontal mesh
82      !
83      CALL dom_zgr               ! Vertical mesh and bathymetry
84      !
85      CALL dom_msk               ! Masks
86      !
87      ht_0(:,:) = e3t_0(:,:,1) * tmask(:,:,1)   ! Reference ocean thickness
88      hu_0(:,:) = e3u_0(:,:,1) * umask(:,:,1)
89      hv_0(:,:) = e3v_0(:,:,1) * vmask(:,:,1)
90      DO jk = 2, jpk
91         ht_0(:,:) = ht_0(:,:) + e3t_0(:,:,jk) * tmask(:,:,jk)
92         hu_0(:,:) = hu_0(:,:) + e3u_0(:,:,jk) * umask(:,:,jk)
93         hv_0(:,:) = hv_0(:,:) + e3v_0(:,:,jk) * vmask(:,:,jk)
94      END DO
95      !
96      CALL cfg_write             ! create the configuration file
97      !
98      CALL dom_wri
99      !
100   END SUBROUTINE dom_init
101
102   SUBROUTINE dom_nam
103      !!----------------------------------------------------------------------
104      !!                     ***  ROUTINE dom_nam  ***
105      !!                   
106      !! ** Purpose :   read domaine namelists and print the variables.
107      !!
108      !! ** input   : - namrun namelist
109      !!              - namdom namelist
110      !!              - namnc4 namelist   ! "key_netcdf4" only
111      !!----------------------------------------------------------------------
112      USE ioipsl
113      NAMELIST/namrun/ cn_ocerst_indir, cn_ocerst_outdir, nn_stocklist, ln_rst_list,                 &
114                       nn_no   , cn_exp   , cn_ocerst_in, cn_ocerst_out, ln_rstart , nn_rstctl ,     &
115         &             nn_it000, nn_itend , nn_date0    , nn_time0     , nn_leapy  , nn_istate ,     &
116         &             nn_stock, nn_write , ln_mskland  , ln_clobber   , nn_chunksz, nn_euler  ,     &
117         &             ln_cfmeta, ln_iscpl
118      NAMELIST/namdom/ nn_bathy, cn_topo, cn_bath, cn_lon, cn_lat, nn_interp,                        &
119         &             rn_bathy , rn_e3zps_min, rn_e3zps_rat, nn_msh, rn_hmin, rn_isfhmin,           &
120         &             rn_atfp , rn_rdt   , nn_closea   , ln_crs      , jphgr_msh ,                  &
121         &             ppglam0, ppgphi0, ppe1_deg, ppe2_deg, ppe1_m, ppe2_m,                         &
122         &             ppsur, ppa0, ppa1, ppkth, ppacr, ppdzmin, pphmax, ldbletanh,                  &
123         &             ppa2, ppkth2, ppacr2
124
125
126
127      INTEGER  ::   ios                 ! Local integer output status for namelist read
128      !!----------------------------------------------------------------------
129
130      REWIND( numnam_ref )              ! Namelist namrun in reference namelist : Parameters of the run
131      READ  ( numnam_ref, namrun, IOSTAT = ios, ERR = 901)
132901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namrun in reference namelist', lwp )
133
134      REWIND( numnam_cfg )              ! Namelist namrun in configuration namelist : Parameters of the run
135      READ  ( numnam_cfg, namrun, IOSTAT = ios, ERR = 902 )
136902   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namrun in configuration namelist', lwp )
137      IF(lwm) WRITE ( numond, namrun )
138      !
139      IF(lwp) THEN                  ! control print
140         WRITE(numout,*)
141         WRITE(numout,*) 'dom_nam  : domain initialization through namelist read'
142         WRITE(numout,*) '~~~~~~~ '
143         WRITE(numout,*) '   Namelist namrun'
144         WRITE(numout,*) '      job number                      nn_no      = ', nn_no
145         WRITE(numout,*) '      experiment name for output      cn_exp     = ', cn_exp
146         WRITE(numout,*) '      file prefix restart input       cn_ocerst_in= ', cn_ocerst_in
147         WRITE(numout,*) '      restart input directory         cn_ocerst_indir= ', cn_ocerst_indir
148         WRITE(numout,*) '      file prefix restart output      cn_ocerst_out= ', cn_ocerst_out
149         WRITE(numout,*) '      restart output directory        cn_ocerst_outdir= ', cn_ocerst_outdir
150         WRITE(numout,*) '      restart logical                 ln_rstart  = ', ln_rstart
151         WRITE(numout,*) '      start with forward time step    nn_euler   = ', nn_euler
152         WRITE(numout,*) '      control of time step            nn_rstctl  = ', nn_rstctl
153         WRITE(numout,*) '      number of the first time step   nn_it000   = ', nn_it000
154         WRITE(numout,*) '      number of the last time step    nn_itend   = ', nn_itend
155         WRITE(numout,*) '      initial calendar date aammjj    nn_date0   = ', nn_date0
156         WRITE(numout,*) '      initial time of day in hhmm     nn_time0   = ', nn_time0
157         WRITE(numout,*) '      leap year calendar (0/1)        nn_leapy   = ', nn_leapy
158         WRITE(numout,*) '      initial state output            nn_istate  = ', nn_istate
159         IF( ln_rst_list ) THEN
160            WRITE(numout,*) '      list of restart dump times      nn_stocklist   =', nn_stocklist
161         ELSE
162            WRITE(numout,*) '      frequency of restart file       nn_stock   = ', nn_stock
163         ENDIF
164         WRITE(numout,*) '      frequency of output file        nn_write   = ', nn_write
165         WRITE(numout,*) '      mask land points                ln_mskland = ', ln_mskland
166         WRITE(numout,*) '      additional CF standard metadata ln_cfmeta  = ', ln_cfmeta
167         WRITE(numout,*) '      overwrite an existing file      ln_clobber = ', ln_clobber
168         WRITE(numout,*) '      NetCDF chunksize (bytes)        nn_chunksz = ', nn_chunksz
169         WRITE(numout,*) '      IS coupling at the restart step ln_iscpl   = ', ln_iscpl
170      ENDIF
171
172      cexper = cn_exp
173      nrstdt = nn_rstctl
174      nit000 = nn_it000
175      nitend = nn_itend
176      ndate0 = nn_date0
177      nleapy = nn_leapy
178      ninist = nn_istate
179      nstock = nn_stock
180      nstocklist = nn_stocklist
181      nwrite = nn_write
182      neuler = nn_euler
183      IF ( neuler == 1 .AND. .NOT. ln_rstart ) THEN
184         WRITE(ctmp1,*) 'ln_rstart =.FALSE., nn_euler is forced to 0 '
185         CALL ctl_warn( ctmp1 )
186         neuler = 0
187      ENDIF
188
189      !                             ! control of output frequency
190      IF ( nstock == 0 .OR. nstock > nitend ) THEN
191         WRITE(ctmp1,*) 'nstock = ', nstock, ' it is forced to ', nitend
192         CALL ctl_warn( ctmp1 )
193         nstock = nitend
194      ENDIF
195      IF ( nwrite == 0 ) THEN
196         WRITE(ctmp1,*) 'nwrite = ', nwrite, ' it is forced to ', nitend
197         CALL ctl_warn( ctmp1 )
198         nwrite = nitend
199      ENDIF
200
201
202
203
204      SELECT CASE ( nleapy )        ! Choose calendar for IOIPSL
205      CASE (  1 ) 
206         CALL ioconf_calendar('gregorian')
207         IF(lwp) WRITE(numout,*) '   The IOIPSL calendar is "gregorian", i.e. leap year'
208      CASE (  0 )
209         CALL ioconf_calendar('noleap')
210         IF(lwp) WRITE(numout,*) '   The IOIPSL calendar is "noleap", i.e. no leap year'
211      CASE ( 30 )
212         CALL ioconf_calendar('360d')
213         IF(lwp) WRITE(numout,*) '   The IOIPSL calendar is "360d", i.e. 360 days in a year'
214      END SELECT
215
216
217
218
219      REWIND( numnam_ref )              ! Namelist namdom in reference namelist : space & time domain (bathymetry, mesh, timestep)
220      READ  ( numnam_ref, namdom, IOSTAT = ios, ERR = 903)
221903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdom in reference namelist', lwp )
222 
223      !
224      REWIND( numnam_cfg )              ! Namelist namdom in configuration namelist : space & time domain (bathymetry, mesh, timestep)
225      READ  ( numnam_cfg, namdom, IOSTAT = ios, ERR = 904 )
226904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdom in configuration namelist', lwp )
227      IF(lwm) WRITE ( numond, namdom )
228      !
229      IF(lwp) THEN
230         WRITE(numout,*)
231         WRITE(numout,*) '   Namelist namdom : space & time domain'
232         WRITE(numout,*) '      flag read/compute bathymetry      nn_bathy     = ', nn_bathy
233         IF( nn_bathy == 2 ) THEN
234            WRITE(numout,*) '      compute bathymetry from file      cn_topo      = ', cn_topo
235         ENDIF   
236         WRITE(numout,*) '      Depth (if =0 bathy=jpkm1)         rn_bathy     = ', rn_bathy
237         WRITE(numout,*) '      min depth of the ocean    (>0) or    rn_hmin   = ', rn_hmin
238         WRITE(numout,*) '      min number of ocean level (<0)       '
239         WRITE(numout,*) '      treshold to open the isf cavity   rn_isfhmin   = ', rn_isfhmin, ' (m)'
240         WRITE(numout,*) '      minimum thickness of partial      rn_e3zps_min = ', rn_e3zps_min, ' (m)'
241         WRITE(numout,*) '         step level                     rn_e3zps_rat = ', rn_e3zps_rat
242         WRITE(numout,*) '      create mesh/mask file(s)          nn_msh       = ', nn_msh
243         WRITE(numout,*) '           = 0   no file created           '
244         WRITE(numout,*) '           = 1   mesh_mask                 '
245         WRITE(numout,*) '           = 2   mesh and mask             '
246         WRITE(numout,*) '           = 3   mesh_hgr, msh_zgr and mask'
247         WRITE(numout,*) '      ocean time step                       rn_rdt    = ', rn_rdt
248         WRITE(numout,*) '      asselin time filter parameter         rn_atfp   = ', rn_atfp
249         WRITE(numout,*) '      suppression of closed seas (=0)       nn_closea = ', nn_closea
250         WRITE(numout,*) '      online coarsening of dynamical fields ln_crs    = ', ln_crs
251         WRITE(numout,*) '      type of horizontal mesh jphgr_msh           = ', jphgr_msh
252         WRITE(numout,*) '      longitude of first raw and column T-point ppglam0 = ', ppglam0
253         WRITE(numout,*) '      latitude  of first raw and column T-point ppgphi0 = ', ppgphi0
254         WRITE(numout,*) '      zonal      grid-spacing (degrees) ppe1_deg        = ', ppe1_deg
255         WRITE(numout,*) '      meridional grid-spacing (degrees) ppe2_deg        = ', ppe2_deg
256         WRITE(numout,*) '      zonal      grid-spacing (degrees) ppe1_m          = ', ppe1_m
257         WRITE(numout,*) '      meridional grid-spacing (degrees) ppe2_m          = ', ppe2_m
258         WRITE(numout,*) '      ORCA r4, r2 and r05 coefficients  ppsur           = ', ppsur
259         WRITE(numout,*) '                                        ppa0            = ', ppa0
260         WRITE(numout,*) '                                        ppa1            = ', ppa1
261         WRITE(numout,*) '                                        ppkth           = ', ppkth
262         WRITE(numout,*) '                                        ppacr           = ', ppacr
263         WRITE(numout,*) '      Minimum vertical spacing ppdzmin                  = ', ppdzmin
264         WRITE(numout,*) '      Maximum depth pphmax                              = ', pphmax
265         WRITE(numout,*) '      Use double tanf function for vertical coordinates ldbletanh = ', ldbletanh
266         WRITE(numout,*) '      Double tanh function parameters ppa2              = ', ppa2
267         WRITE(numout,*) '                                      ppkth2            = ', ppkth2
268         WRITE(numout,*) '                                      ppacr2            = ', ppacr2
269      ENDIF
270      !
271      ntopo     = nn_bathy          ! conversion DOCTOR names into model names (this should disappear soon)
272      e3zps_min = rn_e3zps_min
273      e3zps_rat = rn_e3zps_rat
274      nmsh      = nn_msh
275      atfp      = rn_atfp
276      rdt       = rn_rdt
277
278      snc4set%luse = .FALSE.        ! No NetCDF 4 case
279      !
280   END SUBROUTINE dom_nam
281
282
283   SUBROUTINE dom_ctl
284      !!----------------------------------------------------------------------
285      !!                     ***  ROUTINE dom_ctl  ***
286      !!
287      !! ** Purpose :   Domain control.
288      !!
289      !! ** Method  :   compute and print extrema of masked scale factors
290      !!----------------------------------------------------------------------
291      INTEGER ::   iimi1, ijmi1, iimi2, ijmi2, iima1, ijma1, iima2, ijma2
292      INTEGER, DIMENSION(2) ::   iloc   !
293      REAL(wp) ::   ze1min, ze1max, ze2min, ze2max
294      !!----------------------------------------------------------------------
295      !
296#undef CHECK_DOM
297#ifdef CHECK_DOM
298      IF(lk_mpp) THEN
299         CALL mpp_minloc( e1t(:,:), tmask_i(:,:), ze1min, iimi1,ijmi1 )
300         CALL mpp_minloc( e2t(:,:), tmask_i(:,:), ze2min, iimi2,ijmi2 )
301         CALL mpp_maxloc( e1t(:,:), tmask_i(:,:), ze1max, iima1,ijma1 )
302         CALL mpp_maxloc( e2t(:,:), tmask_i(:,:), ze2max, iima2,ijma2 )
303      ELSE
304         ze1min = MINVAL( e1t(:,:), mask = tmask_i(:,:) == 1._wp )   
305         ze2min = MINVAL( e2t(:,:), mask = tmask_i(:,:) == 1._wp )   
306         ze1max = MAXVAL( e1t(:,:), mask = tmask_i(:,:) == 1._wp )   
307         ze2max = MAXVAL( e2t(:,:), mask = tmask_i(:,:) == 1._wp )   
308
309         iloc  = MINLOC( e1t(:,:), mask = tmask_i(:,:) == 1._wp )
310         iimi1 = iloc(1) + nimpp - 1
311         ijmi1 = iloc(2) + njmpp - 1
312         iloc  = MINLOC( e2t(:,:), mask = tmask_i(:,:) == 1._wp )
313         iimi2 = iloc(1) + nimpp - 1
314         ijmi2 = iloc(2) + njmpp - 1
315         iloc  = MAXLOC( e1t(:,:), mask = tmask_i(:,:) == 1._wp )
316         iima1 = iloc(1) + nimpp - 1
317         ijma1 = iloc(2) + njmpp - 1
318         iloc  = MAXLOC( e2t(:,:), mask = tmask_i(:,:) == 1._wp )
319         iima2 = iloc(1) + nimpp - 1
320         ijma2 = iloc(2) + njmpp - 1
321      ENDIF
322      IF(lwp) THEN
323         WRITE(numout,*)
324         WRITE(numout,*) 'dom_ctl : extrema of the masked scale factors'
325         WRITE(numout,*) '~~~~~~~'
326         WRITE(numout,"(14x,'e1t maxi: ',1f10.2,' at i = ',i5,' j= ',i5)") ze1max, iima1, ijma1
327         WRITE(numout,"(14x,'e1t mini: ',1f10.2,' at i = ',i5,' j= ',i5)") ze1min, iimi1, ijmi1
328         WRITE(numout,"(14x,'e2t maxi: ',1f10.2,' at i = ',i5,' j= ',i5)") ze2max, iima2, ijma2
329         WRITE(numout,"(14x,'e2t mini: ',1f10.2,' at i = ',i5,' j= ',i5)") ze2min, iimi2, ijmi2
330      ENDIF
331#endif
332      !
333   END SUBROUTINE dom_ctl
334
335
336   SUBROUTINE cfg_write
337      !!----------------------------------------------------------------------
338      !!                  ***  ROUTINE cfg_write  ***
339      !!                   
340      !! ** Purpose :   Create the "domain_cfg" file, a NetCDF file which
341      !!              contains all the ocean domain informations required to
342      !!              define an ocean configuration.
343      !!
344      !! ** Method  :   Write in a file all the arrays required to set up an
345      !!              ocean configuration.
346      !!
347      !! ** output file :   domain_cfg.nc : domain size, characteristics,horizontal mesh,
348      !!                              Coriolis parameter, and vertical scale factors
349      !!                              NB: also contains ORCA family information (if cp_cfg = "ORCA")
350      !!                              and depths (ln_e3_dep=F)
351      !!----------------------------------------------------------------------
352      INTEGER           ::   ji, jj, jk   ! dummy loop indices
353      INTEGER           ::   izco, izps, isco, icav
354      INTEGER           ::   inum     ! temprary units for 'domain_cfg.nc' file
355      CHARACTER(len=21) ::   clnam    ! filename (mesh and mask informations)
356      REAL(wp), DIMENSION(jpi,jpj) ::   z2d   ! workspace
357      !!----------------------------------------------------------------------
358      !
359      IF(lwp) WRITE(numout,*)
360      IF(lwp) WRITE(numout,*) 'cfg_write : create the "domain_cfg.nc" file containing all required configuration information'
361      IF(lwp) WRITE(numout,*) '~~~~~~~~~'
362      !
363      !                       ! ============================= !
364      !                       !  create 'domain_cfg.nc' file  !
365      !                       ! ============================= !
366      !         
367      clnam = 'domain_cfg'  ! filename (configuration information)
368      CALL iom_open( TRIM(clnam), inum, ldwrt = .TRUE.)!, kiolib = jprstlib )
369     
370      !
371      !                             !==  ORCA family specificities  ==!
372      IF( cp_cfg == "ORCA" ) THEN
373         CALL iom_rstput( 0, 0, inum, 'ORCA'      , 1._wp            , ktype = jp_i4 )
374         CALL iom_rstput( 0, 0, inum, 'ORCA_index', REAL( jp_cfg, wp), ktype = jp_i4 )         
375      ENDIF
376      !                             !==  global domain size  ==!
377      !
378      CALL iom_rstput( 0, 0, inum, 'jpiglo', REAL( jpiglo, wp), ktype = jp_i4 )
379      CALL iom_rstput( 0, 0, inum, 'jpjglo', REAL( jpjglo, wp), ktype = jp_i4 )
380      CALL iom_rstput( 0, 0, inum, 'jpkglo', REAL( jpk   , wp), ktype = jp_i4 )
381      !
382      !                             !==  domain characteristics  ==!
383      !
384      !                                   ! lateral boundary of the global
385      !                                   domain
386      CALL iom_rstput( 0, 0, inum, 'jperio', REAL( jperio, wp), ktype = jp_i4 )
387      !
388      !                                   ! type of vertical coordinate
389      IF( ln_zco    ) THEN   ;   izco = 1   ;   ELSE   ;   izco = 0   ;   ENDIF
390      IF( ln_zps    ) THEN   ;   izps = 1   ;   ELSE   ;   izps = 0   ;   ENDIF
391      IF( ln_sco    ) THEN   ;   isco = 1   ;   ELSE   ;   isco = 0   ;   ENDIF
392      CALL iom_rstput( 0, 0, inum, 'ln_zco'   , REAL( izco, wp), ktype = jp_i4 )
393      CALL iom_rstput( 0, 0, inum, 'ln_zps'   , REAL( izps, wp), ktype = jp_i4 )
394      CALL iom_rstput( 0, 0, inum, 'ln_sco'   , REAL( isco, wp), ktype = jp_i4 )
395      !
396      !                                   ! ocean cavities under iceshelves
397      IF( ln_isfcav ) THEN   ;   icav = 1   ;   ELSE   ;   icav = 0   ;   ENDIF
398      CALL iom_rstput( 0, 0, inum, 'ln_isfcav', REAL( icav, wp), ktype = jp_i4 )
399      !
400      !                             !==  horizontal mesh  !
401      !
402      CALL iom_rstput( 0, 0, inum, 'glamt', glamt, ktype = jp_r8 )   ! latitude
403      CALL iom_rstput( 0, 0, inum, 'glamu', glamu, ktype = jp_r8 )
404      CALL iom_rstput( 0, 0, inum, 'glamv', glamv, ktype = jp_r8 )
405      CALL iom_rstput( 0, 0, inum, 'glamf', glamf, ktype = jp_r8 )
406      !                               
407      CALL iom_rstput( 0, 0, inum, 'gphit', gphit, ktype = jp_r8 )   ! longitude
408      CALL iom_rstput( 0, 0, inum, 'gphiu', gphiu, ktype = jp_r8 )
409      CALL iom_rstput( 0, 0, inum, 'gphiv', gphiv, ktype = jp_r8 )
410      CALL iom_rstput( 0, 0, inum, 'gphif', gphif, ktype = jp_r8 )
411      !                               
412      CALL iom_rstput( 0, 0, inum, 'e1t'  , e1t  , ktype = jp_r8 )   ! i-scale factors (e1.)
413      CALL iom_rstput( 0, 0, inum, 'e1u'  , e1u  , ktype = jp_r8 )
414      CALL iom_rstput( 0, 0, inum, 'e1v'  , e1v  , ktype = jp_r8 )
415      CALL iom_rstput( 0, 0, inum, 'e1f'  , e1f  , ktype = jp_r8 )
416      !
417      CALL iom_rstput( 0, 0, inum, 'e2t'  , e2t  , ktype = jp_r8 )   ! j-scale factors (e2.)
418      CALL iom_rstput( 0, 0, inum, 'e2u'  , e2u  , ktype = jp_r8 )
419      CALL iom_rstput( 0, 0, inum, 'e2v'  , e2v  , ktype = jp_r8 )
420      CALL iom_rstput( 0, 0, inum, 'e2f'  , e2f  , ktype = jp_r8 )
421      !
422      CALL iom_rstput( 0, 0, inum, 'ff_f' , ff_f , ktype = jp_r8 )   ! coriolis factor
423      CALL iom_rstput( 0, 0, inum, 'ff_t' , ff_t , ktype = jp_r8 )
424      !
425      !                             !==  vertical mesh  ==!
426      !                                                     
427      CALL iom_rstput( 0, 0, inum, 'e3t_1d'  , e3t_1d  , ktype = jp_r8 )   !  reference 1D-coordinate
428      CALL iom_rstput( 0, 0, inum, 'e3w_1d'  , e3w_1d  , ktype = jp_r8 )
429      !
430      CALL iom_rstput( 0, 0, inum, 'e3t_0'   , e3t_0   , ktype = jp_r8 )   !  vertical scale factors (e
431      CALL iom_rstput( 0, 0, inum, 'e3u_0'   , e3u_0   , ktype = jp_r8 )
432      CALL iom_rstput( 0, 0, inum, 'e3v_0'   , e3v_0   , ktype = jp_r8 )
433      CALL iom_rstput( 0, 0, inum, 'e3f_0'   , e3f_0   , ktype = jp_r8 )
434      CALL iom_rstput( 0, 0, inum, 'e3w_0'   , e3w_0   , ktype = jp_r8 )
435      CALL iom_rstput( 0, 0, inum, 'e3uw_0'  , e3uw_0  , ktype = jp_r8 )
436      CALL iom_rstput( 0, 0, inum, 'e3vw_0'  , e3vw_0  , ktype = jp_r8 )
437      !
438      IF(.NOT.ln_e3_dep ) THEN                                             !  depth (t- & w-points)
439         CALL iom_rstput( 0, 0, inum, 'gdept_1d', gdept_1d, ktype = jp_r8 )   ! required only with 
440         CALL iom_rstput( 0, 0, inum, 'gdepw_1d', gdepw_1d, ktype = jp_r8 )   ! the old e3. definition
441         CALL iom_rstput( 0, 0, inum, 'gdept_0' , gdept_0 , ktype = jp_r8 )
442         CALL iom_rstput( 0, 0, inum, 'gdepw_0' , gdepw_0 , ktype = jp_r8 )
443      ENDIF
444      !                                         
445      !                             !==  ocean top and bottom level  ==!
446      !
447      CALL iom_rstput( 0, 0, inum, 'bottom_level' , REAL( mbkt, wp )*ssmask , ktype = jp_i4 )   ! nb of ocean T-points
448      CALL iom_rstput( 0, 0, inum, 'top_level'    , REAL( mikt, wp )*ssmask , ktype = jp_i4 )   ! nb of ocean T-points (ISF)
449      DO jj = 1,jpj
450         DO ji = 1,jpi
451            z2d (ji,jj) = SUM ( e3t_0(ji,jj, 1:mbkt(ji,jj) ) ) * ssmask(ji,jj) 
452         END DO
453      END DO
454      CALL iom_rstput( 0, 0, inum, 'bathy_metry'   , z2d , ktype = jp_r4 )
455
456      !
457      IF( ln_sco ) THEN             ! s-coordinate: store grid stiffness ratio  (Not required anyway)
458         CALL dom_stiff( z2d )
459         CALL iom_rstput( 0, 0, inum, 'stiffness', z2d )        !    ! Max. grid stiffness ratio
460      ENDIF
461      !
462      !                                ! ============================
463      !                                !        close the files
464      !                                ! ============================
465      CALL iom_close( inum )
466      !
467   END SUBROUTINE cfg_write
468
469
470
471   !!======================================================================
472END MODULE domain
Note: See TracBrowser for help on using the repository browser.