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/UKMO_MERGE_2019/src/OCE/DOM – NEMO

source: NEMO/branches/2019/UKMO_MERGE_2019/src/OCE/DOM/domain.F90 @ 12079

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

include ENHANCE-03_closea in UKMO merge branch

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