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/UKMO/dev_r12745_HPC-02_Daley_Tiling_trial_public/src/OCE/DOM – NEMO

source: NEMO/branches/UKMO/dev_r12745_HPC-02_Daley_Tiling_trial_public/src/OCE/DOM/domain.F90 @ 12979

Last change on this file since 12979 was 12979, checked in by hadcv, 4 years ago

Replace references to tile index arrays with scalars

  • Property svn:keywords set to Id
File size: 40.6 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   !!            4.0  !  2016-10  (G. Madec, S. Flavoni)  domain configuration / user defined interface
17   !!----------------------------------------------------------------------
18   
19   !!----------------------------------------------------------------------
20   !!   dom_init      : initialize the space and time domain
21   !!   dom_glo       : initialize global domain <--> local domain indices
22   !!   dom_nam       : read and contral domain namelists
23   !!   dom_ctl       : control print for the ocean domain
24   !!   domain_cfg    : read the global domain size in domain configuration file
25   !!   cfg_write     : create the domain configuration file
26   !!----------------------------------------------------------------------
27   USE oce            ! ocean variables
28   USE dom_oce        ! domain: ocean
29   USE sbc_oce        ! surface boundary condition: ocean
30   USE trc_oce        ! shared ocean & passive tracers variab
31   USE phycst         ! physical constants
32   USE domhgr         ! domain: set the horizontal mesh
33   USE domzgr         ! domain: set the vertical mesh
34   USE dommsk         ! domain: set the mask system
35   USE domwri         ! domain: write the meshmask file
36   USE domvvl         ! variable volume
37   USE c1d            ! 1D configuration
38   USE dyncor_c1d     ! 1D configuration: Coriolis term    (cor_c1d routine)
39   USE wet_dry, ONLY : ll_wd
40   USE closea , ONLY : dom_clo ! closed seas
41   !
42   USE in_out_manager ! I/O manager
43   USE iom            ! I/O library
44   USE lbclnk         ! ocean lateral boundary condition (or mpp link)
45   USE lib_mpp        ! distributed memory computing library
46
47   IMPLICIT NONE
48   PRIVATE
49
50   PUBLIC   dom_init     ! called by nemogcm.F90
51   PUBLIC   domain_cfg   ! called by nemogcm.F90
52   PUBLIC   dom_tile     ! called by step.F90
53
54   !!-------------------------------------------------------------------------
55   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
56   !! $Id$
57   !! Software governed by the CeCILL license (see ./LICENSE)
58   !!-------------------------------------------------------------------------
59CONTAINS
60
61   SUBROUTINE dom_init( Kbb, Kmm, Kaa, cdstr )
62      !!----------------------------------------------------------------------
63      !!                  ***  ROUTINE dom_init  ***
64      !!                   
65      !! ** Purpose :   Domain initialization. Call the routines that are
66      !!              required to create the arrays which define the space
67      !!              and time domain of the ocean model.
68      !!
69      !! ** Method  : - dom_msk: compute the masks from the bathymetry file
70      !!              - dom_hgr: compute or read the horizontal grid-point position
71      !!                         and scale factors, and the coriolis factor
72      !!              - dom_zgr: define the vertical coordinate and the bathymetry
73      !!              - dom_wri: create the meshmask file (ln_meshmask=T)
74      !!              - 1D configuration, move Coriolis, u and v at T-point
75      !!----------------------------------------------------------------------
76      INTEGER          , INTENT(in) :: Kbb, Kmm, Kaa          ! ocean time level indices
77      CHARACTER (len=*), INTENT(in) :: cdstr                  ! model: NEMO or SAS. Determines core restart variables
78      !
79      INTEGER ::   ji, jj, jk, ik   ! dummy loop indices
80      INTEGER ::   iconf = 0    ! local integers
81      CHARACTER (len=64) ::   cform = "(A12, 3(A13, I7))" 
82      INTEGER , DIMENSION(jpi,jpj) ::   ik_top , ik_bot       ! top and bottom ocean level
83      REAL(wp), DIMENSION(jpi,jpj) ::   z1_hu_0, z1_hv_0
84      !!----------------------------------------------------------------------
85      !
86      IF(lwp) THEN         ! Ocean domain Parameters (control print)
87         WRITE(numout,*)
88         WRITE(numout,*) 'dom_init : domain initialization'
89         WRITE(numout,*) '~~~~~~~~'
90         !
91         WRITE(numout,*)     '   Domain info'
92         WRITE(numout,*)     '      dimension of model:'
93         WRITE(numout,*)     '             Local domain      Global domain       Data domain '
94         WRITE(numout,cform) '        ','   jpi     : ', jpi, '   jpiglo  : ', jpiglo
95         WRITE(numout,cform) '        ','   jpj     : ', jpj, '   jpjglo  : ', jpjglo
96         WRITE(numout,cform) '        ','   jpk     : ', jpk, '   jpkglo  : ', jpkglo
97         WRITE(numout,cform) '       ' ,'   jpij    : ', jpij
98         WRITE(numout,*)     '      mpp local domain info (mpp):'
99         WRITE(numout,*)     '              jpni    : ', jpni, '   nn_hls  : ', nn_hls
100         WRITE(numout,*)     '              jpnj    : ', jpnj, '   nn_hls  : ', nn_hls
101         WRITE(numout,*)     '              jpnij   : ', jpnij
102         WRITE(numout,*)     '      lateral boundary of the Global domain : jperio  = ', jperio
103         SELECT CASE ( jperio )
104         CASE( 0 )   ;   WRITE(numout,*) '         (i.e. closed)'
105         CASE( 1 )   ;   WRITE(numout,*) '         (i.e. cyclic east-west)'
106         CASE( 2 )   ;   WRITE(numout,*) '         (i.e. cyclic north-south)'
107         CASE( 3 )   ;   WRITE(numout,*) '         (i.e. north fold with T-point pivot)'
108         CASE( 4 )   ;   WRITE(numout,*) '         (i.e. cyclic east-west and north fold with T-point pivot)'
109         CASE( 5 )   ;   WRITE(numout,*) '         (i.e. north fold with F-point pivot)'
110         CASE( 6 )   ;   WRITE(numout,*) '         (i.e. cyclic east-west and north fold with F-point pivot)'
111         CASE( 7 )   ;   WRITE(numout,*) '         (i.e. cyclic east-west and north-south)'
112         CASE DEFAULT
113            CALL ctl_stop( 'jperio is out of range' )
114         END SELECT
115         WRITE(numout,*)     '      Ocean model configuration used:'
116         WRITE(numout,*)     '         cn_cfg = ', TRIM( cn_cfg ), '   nn_cfg = ', nn_cfg
117      ENDIF
118      lwxios = .FALSE.
119      ln_xios_read = .FALSE.
120      !
121      !           !==  Reference coordinate system  ==!
122      !
123      CALL dom_glo                            ! global domain versus local domain
124      CALL dom_nam                            ! read namelist ( namrun, namdom )
125      CALL dom_tile( ntsi, ntsj, ntei, ntej ) ! Tile domain
126
127      !
128      IF( lwxios ) THEN
129!define names for restart write and set core output (restart.F90)
130         CALL iom_set_rst_vars(rst_wfields)
131         CALL iom_set_rstw_core(cdstr)
132      ENDIF
133!reset namelist for SAS
134      IF(cdstr == 'SAS') THEN
135         IF(lrxios) THEN
136               IF(lwp) write(numout,*) 'Disable reading restart file using XIOS for SAS'
137               lrxios = .FALSE.
138         ENDIF
139      ENDIF
140      !
141      CALL dom_hgr                      ! Horizontal mesh
142
143      IF( ln_closea ) CALL dom_clo      ! Read in masks to define closed seas and lakes
144
145      CALL dom_zgr( ik_top, ik_bot )    ! Vertical mesh and bathymetry
146
147      CALL dom_msk( ik_top, ik_bot )    ! Masks
148      !
149      ht_0(:,:) = 0._wp  ! Reference ocean thickness
150      hu_0(:,:) = 0._wp
151      hv_0(:,:) = 0._wp
152      DO jk = 1, jpk
153         ht_0(:,:) = ht_0(:,:) + e3t_0(:,:,jk) * tmask(:,:,jk)
154         hu_0(:,:) = hu_0(:,:) + e3u_0(:,:,jk) * umask(:,:,jk)
155         hv_0(:,:) = hv_0(:,:) + e3v_0(:,:,jk) * vmask(:,:,jk)
156      END DO
157      !
158      !           !==  time varying part of coordinate system  ==!
159      !
160      IF( ln_linssh ) THEN       != Fix in time : set to the reference one for all
161      !
162         !       before        !          now          !       after         !
163            gdept(:,:,:,Kbb) = gdept_0  ;   gdept(:,:,:,Kmm) = gdept_0   ;   gdept(:,:,:,Kaa) = gdept_0   ! depth of grid-points
164            gdepw(:,:,:,Kbb) = gdepw_0  ;   gdepw(:,:,:,Kmm) = gdepw_0   ;   gdepw(:,:,:,Kaa) = gdepw_0   !
165                                   gde3w = gde3w_0   !        ---          !
166         !                                                                 
167              e3t(:,:,:,Kbb) =   e3t_0  ;     e3t(:,:,:,Kmm) =   e3t_0   ;   e3t(:,:,:,Kaa) =  e3t_0    ! scale factors
168              e3u(:,:,:,Kbb) =   e3u_0  ;     e3u(:,:,:,Kmm) =   e3u_0   ;   e3u(:,:,:,Kaa) =  e3u_0    !
169              e3v(:,:,:,Kbb) =   e3v_0  ;     e3v(:,:,:,Kmm) =   e3v_0   ;   e3v(:,:,:,Kaa) =  e3v_0    !
170                                     e3f =   e3f_0   !        ---          !
171              e3w(:,:,:,Kbb) =   e3w_0  ;     e3w(:,:,:,Kmm) =   e3w_0   ;    e3w(:,:,:,Kaa) =   e3w_0   !
172             e3uw(:,:,:,Kbb) =  e3uw_0  ;    e3uw(:,:,:,Kmm) =  e3uw_0   ;   e3uw(:,:,:,Kaa) =  e3uw_0   
173             e3vw(:,:,:,Kbb) =  e3vw_0  ;    e3vw(:,:,:,Kmm) =  e3vw_0   ;   e3vw(:,:,:,Kaa) =  e3vw_0   !
174         !
175         z1_hu_0(:,:) = ssumask(:,:) / ( hu_0(:,:) + 1._wp - ssumask(:,:) )     ! _i mask due to ISF
176         z1_hv_0(:,:) = ssvmask(:,:) / ( hv_0(:,:) + 1._wp - ssvmask(:,:) )
177         !
178         !        before       !          now          !       after         !
179                                      ht =    ht_0   !                     ! water column thickness
180               hu(:,:,Kbb) =    hu_0  ;      hu(:,:,Kmm) =    hu_0   ;    hu(:,:,Kaa) =    hu_0   !
181               hv(:,:,Kbb) =    hv_0  ;      hv(:,:,Kmm) =    hv_0   ;    hv(:,:,Kaa) =    hv_0   !
182            r1_hu(:,:,Kbb) = z1_hu_0  ;   r1_hu(:,:,Kmm) = z1_hu_0   ; r1_hu(:,:,Kaa) = z1_hu_0   ! inverse of water column thickness
183            r1_hv(:,:,Kbb) = z1_hv_0  ;   r1_hv(:,:,Kmm) = z1_hv_0   ; r1_hv(:,:,Kaa) = z1_hv_0   !
184         !
185         !
186      ELSE                       != time varying : initialize before/now/after variables
187         !
188         IF( .NOT.l_offline )  CALL dom_vvl_init( Kbb, Kmm, Kaa )
189         !
190      ENDIF
191      !
192      IF( lk_c1d         )   CALL cor_c1d       ! 1D configuration: Coriolis set at T-point
193      !
194      IF( ln_meshmask    )   CALL dom_wri       ! Create a domain file
195      IF( .NOT.ln_rstart )   CALL dom_ctl       ! Domain control
196      !
197      IF( ln_write_cfg   )   CALL cfg_write     ! create the configuration file
198      !
199      IF(lwp) THEN
200         WRITE(numout,*)
201         WRITE(numout,*) 'dom_init :   ==>>>   END of domain initialization'
202         WRITE(numout,*) '~~~~~~~~'
203         WRITE(numout,*) 
204      ENDIF
205      !
206   END SUBROUTINE dom_init
207
208
209   SUBROUTINE dom_glo
210      !!----------------------------------------------------------------------
211      !!                     ***  ROUTINE dom_glo  ***
212      !!
213      !! ** Purpose :   initialization of global domain <--> local domain indices
214      !!
215      !! ** Method  :   
216      !!
217      !! ** Action  : - mig , mjg : local  domain indices ==> global domain indices
218      !!              - mi0 , mi1 : global domain indices ==> local  domain indices
219      !!              - mj0,, mj1   (global point not in the local domain ==> mi0>mi1 and/or mj0>mj1)
220      !!----------------------------------------------------------------------
221      INTEGER ::   ji, jj   ! dummy loop argument
222      !!----------------------------------------------------------------------
223      !
224      DO ji = 1, jpi                 ! local domain indices ==> global domain indices
225        mig(ji) = ji + nimpp - 1
226      END DO
227      DO jj = 1, jpj
228        mjg(jj) = jj + njmpp - 1
229      END DO
230      !                              ! global domain indices ==> local domain indices
231      !                                   ! (return (m.0,m.1)=(1,0) if data domain gridpoint is to the west/south of the
232      !                                   ! local domain, or (m.0,m.1)=(jp.+1,jp.) to the east/north of local domain.
233      DO ji = 1, jpiglo
234        mi0(ji) = MAX( 1 , MIN( ji - nimpp + 1, jpi+1 ) )
235        mi1(ji) = MAX( 0 , MIN( ji - nimpp + 1, jpi   ) )
236      END DO
237      DO jj = 1, jpjglo
238        mj0(jj) = MAX( 1 , MIN( jj - njmpp + 1, jpj+1 ) )
239        mj1(jj) = MAX( 0 , MIN( jj - njmpp + 1, jpj   ) )
240      END DO
241      IF(lwp) THEN                   ! control print
242         WRITE(numout,*)
243         WRITE(numout,*) 'dom_glo : domain: global <<==>> local '
244         WRITE(numout,*) '~~~~~~~ '
245         WRITE(numout,*) '   global domain:   jpiglo = ', jpiglo, ' jpjglo = ', jpjglo, ' jpkglo = ', jpkglo
246         WRITE(numout,*) '   local  domain:   jpi    = ', jpi   , ' jpj    = ', jpj   , ' jpk    = ', jpk
247         WRITE(numout,*)
248         WRITE(numout,*) '   conversion from local to global domain indices (and vise versa) done'
249         IF( nn_print >= 1 ) THEN
250            WRITE(numout,*)
251            WRITE(numout,*) '          conversion local  ==> global i-index domain (mig)'
252            WRITE(numout,25)              (mig(ji),ji = 1,jpi)
253            WRITE(numout,*)
254            WRITE(numout,*) '          conversion global ==> local  i-index domain'
255            WRITE(numout,*) '             starting index (mi0)'
256            WRITE(numout,25)              (mi0(ji),ji = 1,jpiglo)
257            WRITE(numout,*) '             ending index (mi1)'
258            WRITE(numout,25)              (mi1(ji),ji = 1,jpiglo)
259            WRITE(numout,*)
260            WRITE(numout,*) '          conversion local  ==> global j-index domain (mjg)'
261            WRITE(numout,25)              (mjg(jj),jj = 1,jpj)
262            WRITE(numout,*)
263            WRITE(numout,*) '          conversion global ==> local  j-index domain'
264            WRITE(numout,*) '             starting index (mj0)'
265            WRITE(numout,25)              (mj0(jj),jj = 1,jpjglo)
266            WRITE(numout,*) '             ending index (mj1)'
267            WRITE(numout,25)              (mj1(jj),jj = 1,jpjglo)
268         ENDIF
269      ENDIF
270 25   FORMAT( 100(10x,19i4,/) )
271      !
272   END SUBROUTINE dom_glo
273
274
275   SUBROUTINE dom_tile( ktsi, ktsj, ktei, ktej, ktile )
276      !!----------------------------------------------------------------------
277      !!                     ***  ROUTINE dom_tile  ***
278      !!
279      !! ** Purpose :   Set tile domain variables
280      !!
281      !! ** Action  : - ktsi, ktsj     : start of internal part of domain
282      !!              - ktei, ktej     : end of internal part of domain
283      !!              - ntile          : current tile number
284      !!              - nijtile        : total number of tiles
285      !!----------------------------------------------------------------------
286      INTEGER, INTENT(out) :: ktsi, ktsj, ktei, ktej      ! Tile domain indices
287      INTEGER, INTENT(in), OPTIONAL :: ktile              ! Tile number
288      INTEGER ::   jt                                     ! dummy loop argument
289      INTEGER ::   iitile, ijtile                         ! Local integers
290      !!----------------------------------------------------------------------
291      IF( PRESENT(ktile) .AND. ln_tile ) THEN
292         ntile = ktile                 ! Set domain indices for tile
293         ktsi = ntsi_a(ktile)
294         ktsj = ntsj_a(ktile)
295         ktei = ntei_a(ktile)
296         ktej = ntej_a(ktile)
297      ELSE
298         ntile = 0                     ! Initialise to full domain
299         nijtile = 1
300         ktsi = 1 + nn_hls
301         ktsj = 1 + nn_hls
302         ktei = jpi - nn_hls
303         ktej = jpj - nn_hls
304
305         IF( ln_tile ) THEN            ! Calculate tile domain indices
306            iitile = (jpi - 2 * nn_hls) / nn_ltile_i       ! Number of tiles
307            ijtile = (jpj - 2 * nn_hls) / nn_ltile_j
308            IF( MOD( jpi - 2 * nn_hls, nn_ltile_i ) /= 0 ) iitile = iitile + 1
309            IF( MOD( jpj - 2 * nn_hls, nn_ltile_j ) /= 0 ) ijtile = ijtile + 1
310
311            nijtile = iitile * ijtile
312            ALLOCATE( ntsi_a(0:nijtile), ntsj_a(0:nijtile), ntei_a(0:nijtile), ntej_a(0:nijtile) )
313
314            ntsi_a(0) = ktsi                               ! Full domain
315            ntsj_a(0) = ktsj
316            ntei_a(0) = ktei
317            ntej_a(0) = ktej
318
319            DO jt = 1, nijtile                             ! Tile domains
320               ntsi_a(jt) = ktsi + nn_ltile_i * MOD(jt - 1, iitile)
321               ntsj_a(jt) = ktsj + nn_ltile_j * ((jt - 1) / iitile)
322               ntei_a(jt) = MIN(ntsi_a(jt) + nn_ltile_i - 1, ktei)
323               ntej_a(jt) = MIN(ntsj_a(jt) + nn_ltile_j - 1, ktej)
324            ENDDO
325         ENDIF
326
327         IF(lwp) THEN                  ! control print
328            WRITE(numout,*)
329            WRITE(numout,*) 'dom_tile : Domain tiling decomposition'
330            WRITE(numout,*) '~~~~~~~~'
331            IF( ln_tile ) THEN
332               WRITE(numout,*) iitile, 'tiles in i'
333               WRITE(numout,*) '    Starting indices'
334               WRITE(numout,*) '        ', (ntsi_a(jt), jt=1, iitile)
335               WRITE(numout,*) '    Ending indices'
336               WRITE(numout,*) '        ', (ntei_a(jt), jt=1, iitile)
337               WRITE(numout,*) ijtile, 'tiles in j'
338               WRITE(numout,*) '    Starting indices'
339               WRITE(numout,*) '        ', (ntsj_a(jt), jt=1, nijtile, iitile)
340               WRITE(numout,*) '    Ending indices'
341               WRITE(numout,*) '        ', (ntej_a(jt), jt=1, nijtile, iitile)
342            ELSE
343               WRITE(numout,*) 'No domain tiling'
344               WRITE(numout,*) '    i indices =', ktsi, ':', ktei
345               WRITE(numout,*) '    j indices =', ktsj, ':', ktej
346            ENDIF
347         ENDIF
348      ENDIF
349   END SUBROUTINE dom_tile
350
351
352   SUBROUTINE dom_nam
353      !!----------------------------------------------------------------------
354      !!                     ***  ROUTINE dom_nam  ***
355      !!                   
356      !! ** Purpose :   read domaine namelists and print the variables.
357      !!
358      !! ** input   : - namrun namelist
359      !!              - namdom namelist
360      !!              - namtile namelist
361      !!              - namnc4 namelist   ! "key_netcdf4" only
362      !!----------------------------------------------------------------------
363      USE ioipsl
364      !!
365      INTEGER  ::   ios   ! Local integer
366      !
367      NAMELIST/namrun/ cn_ocerst_indir, cn_ocerst_outdir, nn_stocklist, ln_rst_list,                 &
368         &             nn_no   , cn_exp   , cn_ocerst_in, cn_ocerst_out, ln_rstart , nn_rstctl ,     &
369         &             nn_it000, nn_itend , nn_date0    , nn_time0     , nn_leapy  , nn_istate ,     &
370         &             nn_stock, nn_write , ln_mskland  , ln_clobber   , nn_chunksz, ln_1st_euler  , &
371         &             ln_cfmeta, ln_xios_read, nn_wxios
372      NAMELIST/namdom/ ln_linssh, rn_Dt, rn_atfp, ln_crs, ln_meshmask
373      NAMELIST/namtile/ ln_tile, nn_ltile_i, nn_ltile_j
374#if defined key_netcdf4
375      NAMELIST/namnc4/ nn_nchunks_i, nn_nchunks_j, nn_nchunks_k, ln_nc4zip
376#endif
377      !!----------------------------------------------------------------------
378      !
379      IF(lwp) THEN
380         WRITE(numout,*)
381         WRITE(numout,*) 'dom_nam : domain initialization through namelist read'
382         WRITE(numout,*) '~~~~~~~ '
383      ENDIF
384      !
385      !
386      READ  ( numnam_ref, namrun, IOSTAT = ios, ERR = 901)
387901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namrun in reference namelist' )
388      READ  ( numnam_cfg, namrun, IOSTAT = ios, ERR = 902 )
389902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namrun in configuration namelist' )
390      IF(lwm) WRITE ( numond, namrun )
391      !
392      IF(lwp) THEN                  ! control print
393         WRITE(numout,*) '   Namelist : namrun   ---   run parameters'
394         WRITE(numout,*) '      Assimilation cycle              nn_no           = ', nn_no
395         WRITE(numout,*) '      experiment name for output      cn_exp          = ', TRIM( cn_exp           )
396         WRITE(numout,*) '      file prefix restart input       cn_ocerst_in    = ', TRIM( cn_ocerst_in     )
397         WRITE(numout,*) '      restart input directory         cn_ocerst_indir = ', TRIM( cn_ocerst_indir  )
398         WRITE(numout,*) '      file prefix restart output      cn_ocerst_out   = ', TRIM( cn_ocerst_out    )
399         WRITE(numout,*) '      restart output directory        cn_ocerst_outdir= ', TRIM( cn_ocerst_outdir )
400         WRITE(numout,*) '      restart logical                 ln_rstart       = ', ln_rstart
401         WRITE(numout,*) '      start with forward time step    ln_1st_euler    = ', ln_1st_euler
402         WRITE(numout,*) '      control of time step            nn_rstctl       = ', nn_rstctl
403         WRITE(numout,*) '      number of the first time step   nn_it000        = ', nn_it000
404         WRITE(numout,*) '      number of the last time step    nn_itend        = ', nn_itend
405         WRITE(numout,*) '      initial calendar date aammjj    nn_date0        = ', nn_date0
406         WRITE(numout,*) '      initial time of day in hhmm     nn_time0        = ', nn_time0
407         WRITE(numout,*) '      leap year calendar (0/1)        nn_leapy        = ', nn_leapy
408         WRITE(numout,*) '      initial state output            nn_istate       = ', nn_istate
409         IF( ln_rst_list ) THEN
410            WRITE(numout,*) '      list of restart dump times      nn_stocklist    =', nn_stocklist
411         ELSE
412            WRITE(numout,*) '      frequency of restart file       nn_stock        = ', nn_stock
413         ENDIF
414#if ! defined key_iomput
415         WRITE(numout,*) '      frequency of output file        nn_write        = ', nn_write
416#endif
417         WRITE(numout,*) '      mask land points                ln_mskland      = ', ln_mskland
418         WRITE(numout,*) '      additional CF standard metadata ln_cfmeta       = ', ln_cfmeta
419         WRITE(numout,*) '      overwrite an existing file      ln_clobber      = ', ln_clobber
420         WRITE(numout,*) '      NetCDF chunksize (bytes)        nn_chunksz      = ', nn_chunksz
421         IF( TRIM(Agrif_CFixed()) == '0' ) THEN
422            WRITE(numout,*) '      READ restart for a single file using XIOS ln_xios_read =', ln_xios_read
423            WRITE(numout,*) '      Write restart using XIOS        nn_wxios   = ', nn_wxios
424         ELSE
425            WRITE(numout,*) "      AGRIF: nn_wxios will be ingored. See setting for parent"
426            WRITE(numout,*) "      AGRIF: ln_xios_read will be ingored. See setting for parent"
427         ENDIF
428      ENDIF
429
430      cexper = cn_exp         ! conversion DOCTOR names into model names (this should disappear soon)
431      nrstdt = nn_rstctl
432      nit000 = nn_it000
433      nitend = nn_itend
434      ndate0 = nn_date0
435      nleapy = nn_leapy
436      ninist = nn_istate
437      l_1st_euler = ln_1st_euler
438      IF( .NOT. l_1st_euler .AND. .NOT. ln_rstart ) THEN
439         IF(lwp) WRITE(numout,*) 
440         IF(lwp) WRITE(numout,*)'   ==>>>   Start from rest (ln_rstart=F)'
441         IF(lwp) WRITE(numout,*)'           an Euler initial time step is used : l_1st_euler is forced to .true. '   
442         l_1st_euler = .true.
443      ENDIF
444      !                             ! control of output frequency
445      IF( .NOT. ln_rst_list ) THEN     ! we use nn_stock
446         IF( nn_stock == -1 )   CALL ctl_warn( 'nn_stock = -1 --> no restart will be done' )
447         IF( nn_stock == 0 .OR. nn_stock > nitend ) THEN
448            WRITE(ctmp1,*) 'nn_stock = ', nn_stock, ' it is forced to ', nitend
449            CALL ctl_warn( ctmp1 )
450            nn_stock = nitend
451         ENDIF
452      ENDIF
453#if ! defined key_iomput
454      IF( nn_write == -1 )   CALL ctl_warn( 'nn_write = -1 --> no output files will be done' )
455      IF ( nn_write == 0 ) THEN
456         WRITE(ctmp1,*) 'nn_write = ', nn_write, ' it is forced to ', nitend
457         CALL ctl_warn( ctmp1 )
458         nn_write = nitend
459      ENDIF
460#endif
461
462#if defined key_agrif
463      IF( Agrif_Root() ) THEN
464#endif
465      IF(lwp) WRITE(numout,*)
466      SELECT CASE ( nleapy )        ! Choose calendar for IOIPSL
467      CASE (  1 ) 
468         CALL ioconf_calendar('gregorian')
469         IF(lwp) WRITE(numout,*) '   ==>>>   The IOIPSL calendar is "gregorian", i.e. leap year'
470      CASE (  0 )
471         CALL ioconf_calendar('noleap')
472         IF(lwp) WRITE(numout,*) '   ==>>>   The IOIPSL calendar is "noleap", i.e. no leap year'
473      CASE ( 30 )
474         CALL ioconf_calendar('360d')
475         IF(lwp) WRITE(numout,*) '   ==>>>   The IOIPSL calendar is "360d", i.e. 360 days in a year'
476      END SELECT
477#if defined key_agrif
478      ENDIF
479#endif
480
481      READ  ( numnam_ref, namdom, IOSTAT = ios, ERR = 903)
482903   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namdom in reference namelist' )
483      READ  ( numnam_cfg, namdom, IOSTAT = ios, ERR = 904 )
484904   IF( ios >  0 )   CALL ctl_nam ( ios , 'namdom in configuration namelist' )
485      IF(lwm) WRITE( numond, namdom )
486      !
487      IF(lwp) THEN
488         WRITE(numout,*)
489         WRITE(numout,*) '   Namelist : namdom   ---   space & time domain'
490         WRITE(numout,*) '      linear free surface (=T)                ln_linssh   = ', ln_linssh
491         WRITE(numout,*) '      create mesh/mask file                   ln_meshmask = ', ln_meshmask
492         WRITE(numout,*) '      ocean time step                         rn_Dt       = ', rn_Dt
493         WRITE(numout,*) '      asselin time filter parameter           rn_atfp     = ', rn_atfp
494         WRITE(numout,*) '      online coarsening of dynamical fields   ln_crs      = ', ln_crs
495      ENDIF
496      !
497      !! Initialise current model timestep rDt = 2*rn_Dt if MLF or rDt = rn_Dt if RK3
498      rDt  = 2._wp * rn_Dt
499      r1_Dt = 1._wp / rDt
500
501      READ  ( numnam_ref, namtile, IOSTAT = ios, ERR = 905 )
502905   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtile in reference namelist' )
503      READ  ( numnam_cfg, namtile, IOSTAT = ios, ERR = 906 )
504906   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtile in configuration namelist' )
505      IF(lwm) WRITE( numond, namtile )
506
507      IF(lwp) THEN
508         WRITE(numout,*)
509         WRITE(numout,*)    '   Namelist : namtile   ---   Domain tiling decomposition'
510         WRITE(numout,*)    '      Tiling (T) or not (F)                ln_tile   = ', ln_tile
511         WRITE(numout,*)    '      Length of tile in i                  nn_ltile_i = ', nn_ltile_i
512         WRITE(numout,*)    '      Length of tile in j                  nn_ltile_j = ', nn_ltile_j
513         WRITE(numout,*)
514         IF( ln_tile ) THEN
515            WRITE(numout,*) '      The domain will be decomposed into tiles of size', nn_ltile_i, 'x', nn_ltile_j
516         ELSE
517            WRITE(numout,*) '      Domain tiling will NOT be used'
518         ENDIF
519      ENDIF
520
521      IF( TRIM(Agrif_CFixed()) == '0' ) THEN
522         lrxios = ln_xios_read.AND.ln_rstart
523!set output file type for XIOS based on NEMO namelist
524         IF (nn_wxios > 0) lwxios = .TRUE. 
525         nxioso = nn_wxios
526      ENDIF
527
528#if defined key_netcdf4
529      !                             ! NetCDF 4 case   ("key_netcdf4" defined)
530      READ  ( numnam_ref, namnc4, IOSTAT = ios, ERR = 907)
531907   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namnc4 in reference namelist' )
532      READ  ( numnam_cfg, namnc4, IOSTAT = ios, ERR = 908 )
533908   IF( ios >  0 )   CALL ctl_nam ( ios , 'namnc4 in configuration namelist' )
534      IF(lwm) WRITE( numond, namnc4 )
535
536      IF(lwp) THEN                        ! control print
537         WRITE(numout,*)
538         WRITE(numout,*) '   Namelist namnc4 - Netcdf4 chunking parameters'
539         WRITE(numout,*) '      number of chunks in i-dimension             nn_nchunks_i = ', nn_nchunks_i
540         WRITE(numout,*) '      number of chunks in j-dimension             nn_nchunks_j = ', nn_nchunks_j
541         WRITE(numout,*) '      number of chunks in k-dimension             nn_nchunks_k = ', nn_nchunks_k
542         WRITE(numout,*) '      apply netcdf4/hdf5 chunking & compression   ln_nc4zip    = ', ln_nc4zip
543      ENDIF
544
545      ! Put the netcdf4 settings into a simple structure (snc4set, defined in in_out_manager module)
546      ! Note the chunk size in the unlimited (time) dimension will be fixed at 1
547      snc4set%ni   = nn_nchunks_i
548      snc4set%nj   = nn_nchunks_j
549      snc4set%nk   = nn_nchunks_k
550      snc4set%luse = ln_nc4zip
551#else
552      snc4set%luse = .FALSE.        ! No NetCDF 4 case
553#endif
554      !
555   END SUBROUTINE dom_nam
556
557
558   SUBROUTINE dom_ctl
559      !!----------------------------------------------------------------------
560      !!                     ***  ROUTINE dom_ctl  ***
561      !!
562      !! ** Purpose :   Domain control.
563      !!
564      !! ** Method  :   compute and print extrema of masked scale factors
565      !!----------------------------------------------------------------------
566      INTEGER, DIMENSION(2) ::   imi1, imi2, ima1, ima2
567      INTEGER, DIMENSION(2) ::   iloc   !
568      REAL(wp) ::   ze1min, ze1max, ze2min, ze2max
569      !!----------------------------------------------------------------------
570      !
571      IF(lk_mpp) THEN
572         CALL mpp_minloc( 'domain', e1t(:,:), tmask_i(:,:), ze1min, imi1 )
573         CALL mpp_minloc( 'domain', e2t(:,:), tmask_i(:,:), ze2min, imi2 )
574         CALL mpp_maxloc( 'domain', e1t(:,:), tmask_i(:,:), ze1max, ima1 )
575         CALL mpp_maxloc( 'domain', e2t(:,:), tmask_i(:,:), ze2max, ima2 )
576      ELSE
577         ze1min = MINVAL( e1t(:,:), mask = tmask_i(:,:) == 1._wp )   
578         ze2min = MINVAL( e2t(:,:), mask = tmask_i(:,:) == 1._wp )   
579         ze1max = MAXVAL( e1t(:,:), mask = tmask_i(:,:) == 1._wp )   
580         ze2max = MAXVAL( e2t(:,:), mask = tmask_i(:,:) == 1._wp )   
581         !
582         iloc  = MINLOC( e1t(:,:), mask = tmask_i(:,:) == 1._wp )
583         imi1(1) = iloc(1) + nimpp - 1
584         imi1(2) = iloc(2) + njmpp - 1
585         iloc  = MINLOC( e2t(:,:), mask = tmask_i(:,:) == 1._wp )
586         imi2(1) = iloc(1) + nimpp - 1
587         imi2(2) = iloc(2) + njmpp - 1
588         iloc  = MAXLOC( e1t(:,:), mask = tmask_i(:,:) == 1._wp )
589         ima1(1) = iloc(1) + nimpp - 1
590         ima1(2) = iloc(2) + njmpp - 1
591         iloc  = MAXLOC( e2t(:,:), mask = tmask_i(:,:) == 1._wp )
592         ima2(1) = iloc(1) + nimpp - 1
593         ima2(2) = iloc(2) + njmpp - 1
594      ENDIF
595      IF(lwp) THEN
596         WRITE(numout,*)
597         WRITE(numout,*) 'dom_ctl : extrema of the masked scale factors'
598         WRITE(numout,*) '~~~~~~~'
599         WRITE(numout,"(14x,'e1t maxi: ',1f10.2,' at i = ',i5,' j= ',i5)") ze1max, ima1(1), ima1(2)
600         WRITE(numout,"(14x,'e1t mini: ',1f10.2,' at i = ',i5,' j= ',i5)") ze1min, imi1(1), imi1(2)
601         WRITE(numout,"(14x,'e2t maxi: ',1f10.2,' at i = ',i5,' j= ',i5)") ze2max, ima2(1), ima2(2)
602         WRITE(numout,"(14x,'e2t mini: ',1f10.2,' at i = ',i5,' j= ',i5)") ze2min, imi2(1), imi2(2)
603      ENDIF
604      !
605   END SUBROUTINE dom_ctl
606
607
608   SUBROUTINE domain_cfg( cd_cfg, kk_cfg, kpi, kpj, kpk, kperio )
609      !!----------------------------------------------------------------------
610      !!                     ***  ROUTINE dom_nam  ***
611      !!                   
612      !! ** Purpose :   read the domain size in domain configuration file
613      !!
614      !! ** Method  :   read the cn_domcfg NetCDF file
615      !!----------------------------------------------------------------------
616      CHARACTER(len=*)              , INTENT(out) ::   cd_cfg          ! configuration name
617      INTEGER                       , INTENT(out) ::   kk_cfg          ! configuration resolution
618      INTEGER                       , INTENT(out) ::   kpi, kpj, kpk   ! global domain sizes
619      INTEGER                       , INTENT(out) ::   kperio          ! lateral global domain b.c.
620      !
621      INTEGER ::   inum   ! local integer
622      REAL(wp) ::   zorca_res                     ! local scalars
623      REAL(wp) ::   zperio                        !   -      -
624      INTEGER, DIMENSION(4) ::   idvar, idimsz    ! size   of dimensions
625      !!----------------------------------------------------------------------
626      !
627      IF(lwp) THEN
628         WRITE(numout,*) '           '
629         WRITE(numout,*) 'domain_cfg : domain size read in ', TRIM( cn_domcfg ), ' file'
630         WRITE(numout,*) '~~~~~~~~~~ '
631      ENDIF
632      !
633      CALL iom_open( cn_domcfg, inum )
634      !
635      !                                   !- ORCA family specificity
636      IF(  iom_varid( inum, 'ORCA'       , ldstop = .FALSE. ) > 0  .AND.  &
637         & iom_varid( inum, 'ORCA_index' , ldstop = .FALSE. ) > 0    ) THEN
638         !
639         cd_cfg = 'ORCA'
640         CALL iom_get( inum, 'ORCA_index', zorca_res )   ;   kk_cfg = NINT( zorca_res )
641         !
642         IF(lwp) THEN
643            WRITE(numout,*) '   .'
644            WRITE(numout,*) '   ==>>>   ORCA configuration '
645            WRITE(numout,*) '   .'
646         ENDIF
647         !
648      ELSE                                !- cd_cfg & k_cfg are not used
649         cd_cfg = 'UNKNOWN'
650         kk_cfg = -9999999
651                                          !- or they may be present as global attributes
652                                          !- (netcdf only) 
653         CALL iom_getatt( inum, 'cn_cfg', cd_cfg )  ! returns   !  if not found
654         CALL iom_getatt( inum, 'nn_cfg', kk_cfg )  ! returns -999 if not found
655         IF( TRIM(cd_cfg) == '!') cd_cfg = 'UNKNOWN'
656         IF( kk_cfg == -999     ) kk_cfg = -9999999
657         !
658      ENDIF
659       !
660      idvar = iom_varid( inum, 'e3t_0', kdimsz = idimsz )   ! use e3t_0, that must exist, to get jp(ijk)glo
661      kpi = idimsz(1)
662      kpj = idimsz(2)
663      kpk = idimsz(3)
664      CALL iom_get( inum, 'jperio', zperio )   ;   kperio = NINT( zperio )
665      CALL iom_close( inum )
666      !
667      IF(lwp) THEN
668         WRITE(numout,*) '      cn_cfg = ', TRIM(cd_cfg), '   nn_cfg = ', kk_cfg
669         WRITE(numout,*) '      jpiglo = ', kpi
670         WRITE(numout,*) '      jpjglo = ', kpj
671         WRITE(numout,*) '      jpkglo = ', kpk
672         WRITE(numout,*) '      type of global domain lateral boundary   jperio = ', kperio
673      ENDIF
674      !       
675   END SUBROUTINE domain_cfg
676   
677   
678   SUBROUTINE cfg_write
679      !!----------------------------------------------------------------------
680      !!                  ***  ROUTINE cfg_write  ***
681      !!                   
682      !! ** Purpose :   Create the "cn_domcfg_out" file, a NetCDF file which
683      !!              contains all the ocean domain informations required to
684      !!              define an ocean configuration.
685      !!
686      !! ** Method  :   Write in a file all the arrays required to set up an
687      !!              ocean configuration.
688      !!
689      !! ** output file :   domcfg_out.nc : domain size, characteristics, horizontal
690      !!                       mesh, Coriolis parameter, and vertical scale factors
691      !!                    NB: also contain ORCA family information
692      !!----------------------------------------------------------------------
693      INTEGER           ::   ji, jj, jk   ! dummy loop indices
694      INTEGER           ::   izco, izps, isco, icav
695      INTEGER           ::   inum     ! local units
696      CHARACTER(len=21) ::   clnam    ! filename (mesh and mask informations)
697      REAL(wp), DIMENSION(jpi,jpj) ::   z2d   ! workspace
698      !!----------------------------------------------------------------------
699      !
700      IF(lwp) WRITE(numout,*)
701      IF(lwp) WRITE(numout,*) 'cfg_write : create the domain configuration file (', TRIM(cn_domcfg_out),'.nc)'
702      IF(lwp) WRITE(numout,*) '~~~~~~~~~'
703      !
704      !                       ! ============================= !
705      !                       !  create 'domcfg_out.nc' file  !
706      !                       ! ============================= !
707      !         
708      clnam = cn_domcfg_out  ! filename (configuration information)
709      CALL iom_open( TRIM(clnam), inum, ldwrt = .TRUE. )
710     
711      !
712      !                             !==  ORCA family specificities  ==!
713      IF( cn_cfg == "ORCA" ) THEN
714         CALL iom_rstput( 0, 0, inum, 'ORCA'      , 1._wp            , ktype = jp_i4 )
715         CALL iom_rstput( 0, 0, inum, 'ORCA_index', REAL( nn_cfg, wp), ktype = jp_i4 )         
716      ENDIF
717      !
718      !                             !==  global domain size  ==!
719      !
720      CALL iom_rstput( 0, 0, inum, 'jpiglo', REAL( jpiglo, wp), ktype = jp_i4 )
721      CALL iom_rstput( 0, 0, inum, 'jpjglo', REAL( jpjglo, wp), ktype = jp_i4 )
722      CALL iom_rstput( 0, 0, inum, 'jpkglo', REAL( jpk   , wp), ktype = jp_i4 )
723      !
724      !                             !==  domain characteristics  ==!
725      !
726      !                                   ! lateral boundary of the global domain
727      CALL iom_rstput( 0, 0, inum, 'jperio', REAL( jperio, wp), ktype = jp_i4 )
728      !
729      !                                   ! type of vertical coordinate
730      IF( ln_zco    ) THEN   ;   izco = 1   ;   ELSE   ;   izco = 0   ;   ENDIF
731      IF( ln_zps    ) THEN   ;   izps = 1   ;   ELSE   ;   izps = 0   ;   ENDIF
732      IF( ln_sco    ) THEN   ;   isco = 1   ;   ELSE   ;   isco = 0   ;   ENDIF
733      CALL iom_rstput( 0, 0, inum, 'ln_zco'   , REAL( izco, wp), ktype = jp_i4 )
734      CALL iom_rstput( 0, 0, inum, 'ln_zps'   , REAL( izps, wp), ktype = jp_i4 )
735      CALL iom_rstput( 0, 0, inum, 'ln_sco'   , REAL( isco, wp), ktype = jp_i4 )
736      !
737      !                                   ! ocean cavities under iceshelves
738      IF( ln_isfcav ) THEN   ;   icav = 1   ;   ELSE   ;   icav = 0   ;   ENDIF
739      CALL iom_rstput( 0, 0, inum, 'ln_isfcav', REAL( icav, wp), ktype = jp_i4 )
740      !
741      !                             !==  horizontal mesh  !
742      !
743      CALL iom_rstput( 0, 0, inum, 'glamt', glamt, ktype = jp_r8 )   ! latitude
744      CALL iom_rstput( 0, 0, inum, 'glamu', glamu, ktype = jp_r8 )
745      CALL iom_rstput( 0, 0, inum, 'glamv', glamv, ktype = jp_r8 )
746      CALL iom_rstput( 0, 0, inum, 'glamf', glamf, ktype = jp_r8 )
747      !                               
748      CALL iom_rstput( 0, 0, inum, 'gphit', gphit, ktype = jp_r8 )   ! longitude
749      CALL iom_rstput( 0, 0, inum, 'gphiu', gphiu, ktype = jp_r8 )
750      CALL iom_rstput( 0, 0, inum, 'gphiv', gphiv, ktype = jp_r8 )
751      CALL iom_rstput( 0, 0, inum, 'gphif', gphif, ktype = jp_r8 )
752      !                               
753      CALL iom_rstput( 0, 0, inum, 'e1t'  , e1t  , ktype = jp_r8 )   ! i-scale factors (e1.)
754      CALL iom_rstput( 0, 0, inum, 'e1u'  , e1u  , ktype = jp_r8 )
755      CALL iom_rstput( 0, 0, inum, 'e1v'  , e1v  , ktype = jp_r8 )
756      CALL iom_rstput( 0, 0, inum, 'e1f'  , e1f  , ktype = jp_r8 )
757      !
758      CALL iom_rstput( 0, 0, inum, 'e2t'  , e2t  , ktype = jp_r8 )   ! j-scale factors (e2.)
759      CALL iom_rstput( 0, 0, inum, 'e2u'  , e2u  , ktype = jp_r8 )
760      CALL iom_rstput( 0, 0, inum, 'e2v'  , e2v  , ktype = jp_r8 )
761      CALL iom_rstput( 0, 0, inum, 'e2f'  , e2f  , ktype = jp_r8 )
762      !
763      CALL iom_rstput( 0, 0, inum, 'ff_f' , ff_f , ktype = jp_r8 )   ! coriolis factor
764      CALL iom_rstput( 0, 0, inum, 'ff_t' , ff_t , ktype = jp_r8 )
765      !
766      !                             !==  vertical mesh  ==!
767      !                                                     
768      CALL iom_rstput( 0, 0, inum, 'e3t_1d'  , e3t_1d , ktype = jp_r8 )   ! reference 1D-coordinate
769      CALL iom_rstput( 0, 0, inum, 'e3w_1d'  , e3w_1d , ktype = jp_r8 )
770      !
771      CALL iom_rstput( 0, 0, inum, 'e3t_0'   , e3t_0  , ktype = jp_r8 )   ! vertical scale factors
772      CALL iom_rstput( 0, 0, inum, 'e3u_0'   , e3u_0  , ktype = jp_r8 )
773      CALL iom_rstput( 0, 0, inum, 'e3v_0'   , e3v_0  , ktype = jp_r8 )
774      CALL iom_rstput( 0, 0, inum, 'e3f_0'   , e3f_0  , ktype = jp_r8 )
775      CALL iom_rstput( 0, 0, inum, 'e3w_0'   , e3w_0  , ktype = jp_r8 )
776      CALL iom_rstput( 0, 0, inum, 'e3uw_0'  , e3uw_0 , ktype = jp_r8 )
777      CALL iom_rstput( 0, 0, inum, 'e3vw_0'  , e3vw_0 , ktype = jp_r8 )
778      !                                         
779      !                             !==  wet top and bottom level  ==!   (caution: multiplied by ssmask)
780      !
781      CALL iom_rstput( 0, 0, inum, 'top_level'    , REAL( mikt, wp )*ssmask , ktype = jp_i4 )   ! nb of ocean T-points (ISF)
782      CALL iom_rstput( 0, 0, inum, 'bottom_level' , REAL( mbkt, wp )*ssmask , ktype = jp_i4 )   ! nb of ocean T-points
783      !
784      IF( ln_sco ) THEN             ! s-coordinate: store grid stiffness ratio  (Not required anyway)
785         CALL dom_stiff( z2d )
786         CALL iom_rstput( 0, 0, inum, 'stiffness', z2d )        !    ! Max. grid stiffness ratio
787      ENDIF
788      !
789      IF( ll_wd ) THEN              ! wetting and drying domain
790         CALL iom_rstput( 0, 0, inum, 'ht_0'   , ht_0   , ktype = jp_r8 )
791      ENDIF
792      !
793      ! Add some global attributes ( netcdf only )
794      CALL iom_putatt( inum, 'nn_cfg', nn_cfg )
795      CALL iom_putatt( inum, 'cn_cfg', TRIM(cn_cfg) )
796      !
797      !                                ! ============================
798      !                                !        close the files
799      !                                ! ============================
800      CALL iom_close( inum )
801      !
802   END SUBROUTINE cfg_write
803
804   !!======================================================================
805END MODULE domain
Note: See TracBrowser for help on using the repository browser.