source: TOOLS/MOZAIC/src/MOZAIC/inipar.f90 @ 3918

Last change on this file since 3918 was 3918, checked in by omamce, 6 years ago

O.M. : change espfrac from fortran parameter to parameter read in run.def

File size: 22.4 KB
Line 
1! -Mode: f90 -*-
2!!
3MODULE mod_inipar
4   !> prefixture du fichier de definitions
5CONTAINS
6   SUBROUTINE inipar
7      !!
8      USE defprec
9      USE dimensions
10      USE fliocom
11      USE getincom
12      USE errioipsl
13      !!
14      IMPLICIT NONE
15      INTEGER (kind=il)  :: ierr
16      CHARACTER (lEN=80) :: cn_arg
17      CHARACTER (LEN=LEN(c_suffix)) :: cl_suffix
18      !
19      WRITE (nout, *) 'Types par defaut : '
20      WRITE (nout, *) 'INTEGER : ', i_std
21      WRITE (nout, *) 'REAL    : ', r_std
22      !
23      !!
24      !Config Key  = c_suffix
25      !Config Desc = Rajoute un suffixe a tous les noms de fichiers
26      !Config Help =
27      !Config Def  = 'none'
28      c_suffix = 'none'
29      CALL getin ('c_suffix', cl_suffix)
30      IF ( LEN_TRIM (cl_suffix) == 0 .OR. TRIM(cl_suffix) == 'none' ) THEN
31         c_suffix = ''
32      ELSE
33         c_suffix = '_' // TRIM(cl_suffix)
34      END IF
35      WRITE (unit=nout, fmt=*) 'cl_suffix : ', TRIM(cl_suffix)
36      WRITE (unit=nout, fmt=*) 'c_suffix : ', TRIM(c_suffix)
37
38      !Config Key  = c_comment
39      !Config Desc = Rajoute un commentaire dans tous les fichiers NetCDF
40      !Config Help =
41      !Config Def  = 'none'
42      c_comment = 'none'
43      CALL getin ('c_comment', c_comment)
44      WRITE (unit=nout, fmt=*) 'c_comment : ', TRIM(c_comment)
45
46      !!
47      !Config Key  = l_ipsldbg
48      !Config Desc = Pour mettre IOIPSL en mode debug.
49      !Config Help =
50      !Config Def  = n
51      l_ipsldbg= .FALSE.
52      CALL getin ('l_ipsldbg', l_ipsldbg)
53      WRITE (unit=nout, fmt=*) 'l_ipsldbg = ', l_ipsldbg
54      CALL ipsldbg (l_ipsldbg)
55      !!
56      !Config Key  = l_d_alloc
57      !Config Desc = pour suivre les allocs memoire
58      !Config Help =
59      !Config Def  = n
60      l_d_alloc = .FALSE.
61      CALL getin ('l_d_alloc', l_d_alloc)
62      WRITE (unit=nout, fmt=*) 'l_d_alloc = ', l_d_alloc
63      !
64      !Config Key  = l_fast
65      !Config Desc = Pour tester les I/O : calcul rapide de poids
66      !Config Help =
67      !Config Def  = n
68      l_fast = .FALSE.
69      CALL getin ('l_fast', l_fast)
70      WRITE (unit=nout, fmt=*) 'l_fast = ', l_fast
71      !Config Key  = l_dryrun
72      !Config Desc = Pour tester les I/O : pas de calcul de poids.
73      !Config Help =
74      !Config Def  = n
75      l_dryrun= .FALSE.
76      CALL getin ('l_dryrun', l_dryrun)
77      WRITE (unit=nout, fmt=*) 'l_dryrun = ', l_dryrun
78      !Config Key  = lev_dry
79      !Config Desc = Type de test
80      !Config Help =
81      !Config Def  = 1
82      lev_dry= 1
83      CALL getin ('lev_dry', lev_dry)
84      WRITE (unit=nout, fmt=*) 'lev_dry = ', lev_dry
85      !!
86      !! Define ocean model
87      !!
88      !Config Key  = c_period
89      !Config Help =
90      !Config Def  = 'none'
91      c_period = 'none'
92      CALL getin ('c_period', c_period)
93      WRITE (unit=nout, fmt=*) 'c_period = ', c_period
94      !!
95      !Config Key  = jpoi
96      !Config Desc = ocean x dimension
97      !Config Help =
98      !Config Def  = 0
99      CALL getin ('jpoi', jpoi)
100      !Config Key  = jpoj
101      !Config Desc = ocean y dimension
102      !Config Help =
103      !Config Def  = 0
104      CALL getin ('jpoj', jpoj)
105      WRITE (unit=nout, fmt=*) 'jpoi = ', jpoi, ' jpoj = ', jpoj
106      !Config Key  = comod
107      !Config Desc = ocean model name
108      !Config Help =
109      !Config Def  = opa
110      CALL getin ('comod', comod)
111      !Config Key  = cotyp
112      !Config Desc = ocean model type
113      !Config Help =
114      !Config Def  = orca2
115      cotyp = 'orca2'
116      CALL getin ('cotyp', cotyp)
117      WRITE (unit=nout, fmt=*) 'cotyp = ', cotyp
118      !Config Key  = jpoe
119      !Config Desc = number of edges for ocean
120      !Config Def  = 9
121      !Config Help = Number (maxi) of edges to describe ocean box
122      jpoe = 9_il
123      CALL getin ('jpoe', jpoe)
124      WRITE (unit=nout, fmt=*) 'jpoe = ', jpoe
125      !Config Key  = noperio
126      !Config Desc = ocean periodicity type
127      !Config Def  = 4
128      !Config Help = Number (maxi) of edges to describe ocean box
129      noperio = 4_il
130      CALL getin ('noperio', noperio)
131      WRITE (unit=nout, fmt=*) 'noperio = ', noperio 
132      !Config Key  = l_recalc_o
133      !Config Desc = Recompute ocean surfaces
134      !Config Def  = y
135      !Config Help = Recompute ocean surfaces
136      l_recalc_o = .TRUE.
137      CALL getin ('l_recalc_o', l_recalc_o)
138      WRITE (unit=nout, fmt=*) 'l_recalc_o = ', l_recalc_o
139      !Config Key  = c_oce_msk_file
140      !Config Desc = File containing basin mask for ocean
141      !Config Def  = eORCA1.2.nc
142      !Config Help = File containing basin mask for ocean
143      c_oce_msk_file = 'eORCA1.2.nc'
144      CALL getin ('c_oce_msk_file', c_oce_msk_file)
145      WRITE (unit=nout, fmt=*) 'c_oce_msk_file = ', TRIM(c_oce_msk_file)
146      !!
147      !! Define atmosphere model
148      !Config Key  = jpai
149      !Config Desc = atm x dimension
150      !Config Help =
151      !Config Def  = 0
152      CALL getin ('jpai', jpai)
153      !Config Key  = jpaj
154      !Config Desc = atm y dimension
155      !Config Help =
156      !Config Def  = 0
157      CALL getin ('jpaj', jpaj)
158      jpait = jpai   ; jpajt = jpaj+1
159      jpaiu = jpai+1 ; jpaju = jpaj+1
160      jpaiv = jpai+1 ; jpajv = jpaj
161
162      jpaj = jpaj+1
163      WRITE (unit=nout, fmt=*) 'jpai  = ', jpai , ' jpaj  = ', jpaj
164      WRITE (unit=nout, fmt=*) 'jpait = ', jpait, ' jpajt = ', jpajt
165      WRITE (unit=nout, fmt=*) 'jpaiu = ', jpaiu, ' jpaju = ', jpaju
166      WRITE (unit=nout, fmt=*) 'jpaiv = ', jpaiv, ' jpajv = ', jpajv
167
168
169      !Config Key  = camod
170      !Config Desc = atm model name
171      !Config Help =
172      !Config Def  = lmd
173      CALL getin ('camod', camod)
174      WRITE (unit=nout, fmt=*) 'comod = ', comod
175      !Config Key  = catyp
176      !Config Desc = atm model type
177      !Config Help =
178      !Config Def  = lmdz
179      catyp = 'lmdz'
180      CALL getin ('catyp', catyp)
181      WRITE (unit=nout, fmt=*) 'catyp = ', catyp
182      !Config Key  = jpae
183      !Config Desc = number of edges for atm
184      !Config Def  = 9
185      !Config Help = Number (maxi) of edges to describe atm box
186      jpae = 9_il
187      CALL getin ('jpae', jpae)
188      WRITE (unit=nout, fmt=*) 'jpae = ', jpae
189      !Config Key  = naperio
190      !Config Desc = atm periodicity type
191      !Config Def  = -1
192      !Config Help = Number (maxi) of edges to describe ocean box
193      naperio = -1_il
194      CALL getin ('naperio', naperio)
195      WRITE (UNIT=nout, FMT=*) 'naperio = ', naperio 
196     
197      !Config Key  = la_nortop
198      !Config Desc = atm latitudes orientation in masks.nc, areas.nc, grids.nc
199      !Config Def  = .TRUE.
200      !Config Help = .TRUE. increasing latitudes
201      la_nortop = .TRUE.
202      CALL getin ('la_nortop', la_nortop)
203      WRITE (unit=nout, fmt=*) 'la_nortop = ', la_nortop
204
205      !Config Key  = l_recalc_a
206      !Config Desc = Recompute atm surfaces
207      !Config Def  = y
208      !Config Help = Recompute atm surfaces
209      l_recalc_a = .TRUE.
210      CALL getin ('l_recalc_a', l_recalc_a)
211      WRITE (unit=nout, fmt=*) 'l_recalc_a = ', l_recalc_a
212     
213      !Config Key  = la_pole
214      !Config Desc special handing of atm pole point
215      !Config Def  = y
216      la_pole = .FALSE.
217      CALL getin ( 'la_pole', la_pole)
218      WRITE (unit=nout, fmt=*) 'la_pole = ', la_pole
219
220      !Config Key = o2a_orien
221      !Config Desc  = orientation for o2a diag file
222      !Config Def  = nord_en_haut
223      o2a_orien = "nord_en_haut"
224      CALL getin ( 'o2a_orien', o2a_orien)
225      WRITE (unit=nout, fmt=*) 'o2a_orien = ', TRIM(o2a_orien)
226
227      !Config Key  = lmaska
228      !Config Desc = If TRUE, masked points of atmospheric grid (land) are considered for computing.
229      !Config Def  = y
230      lmaska = .TRUE.
231      CALL getin ( 'lmaska', lmaska)
232      WRITE (unit=nout, fmt=*) 'lmaska = ', lmaska
233     
234      !Config Key  = lmasko
235      !Config Desc = If TRUE, masked points of ocean grid (land) are considered for computing.
236      !Config Def  = n
237      lmasko = .FALSE.
238      CALL getin ( 'lmasko', lmasko)
239      WRITE (unit=nout, fmt=*) 'lmasko = ', lmasko
240     
241      !Config Key  = lwro2a
242      !Config Desc = TRUE if oce -> atm weights/adresses are computed
243      !Config Def  = y
244      lwro2a = .TRUE.
245      CALL getin ( 'lwro2a', lwro2a)
246      WRITE (unit=nout, fmt=*) 'lwro2a = ', lwro2a
247
248      !Config Key  = lwra2o
249      !Config Desc = TRUE if atm -> oce weights/adresses are computed
250      !Config Def  = y
251      lwra2o = .TRUE.
252      CALL getin ( 'lwra2o', lwra2o)
253      WRITE (unit=nout, fmt=*) 'lwra2o = ', lwra2o
254     
255      !Config Key  = normo2a
256      !Config Desc = Type of normalization oce -> atm: 0: none, 1: intensive, 2: extensive
257      !Config Def  = 1
258      normo2a = 1
259      CALL getin ( 'normo2a', normo2a)
260      WRITE (unit=nout, fmt=*) 'normo2a = ', normo2a
261
262      !Config Key  = norma2o
263      !Config Desc = Type of normalization atm->oce : 0: none, 1: intensive, 2: extensive
264      !Config Def  = 1
265      norma2o = 1
266      CALL getin ( 'norma2o', norma2o)
267      WRITE (unit=nout, fmt=*) 'norma2o = ', norma2o
268
269!!!
270      !Config Key = jpa2o
271      !Config Desc = max number of neighbors of a->o weights
272      !Config Help =
273      !Config Def = 0
274      CALL getin ('jpa2o', jpa2o)
275      WRITE (UNIT=nout, FMT=*) 'jpa2o = ', jpa2O 
276      !Config Key = jpo2a
277      !Config Desc = max number of neighbors of o-> weights
278      !Config Help =
279      !Config Def = 0
280      CALL getin ('jpo2a', jpo2a)
281      WRITE (UNIT=nout, FMT=*) 'jpo2a = ', jpo2a 
282      !!
283      !Config Key = jma2o
284      !Config Desc = number of neighbors of a->o weights (fluxes)
285      !Config Help =
286      !Config Def = 0
287      jma2o = jpa2o
288      CALL getin ('jma2o', jma2o)
289      WRITE (UNIT=nout, FMT=*) 'jma2o = ', jma2o 
290      !Config Key = jma2or
291      !Config Desc = number of neighbors of a->o weights (runoff)
292      !Config Help =
293      !Config Def = 0
294      jma2or = jpa2o
295      CALL getin ('jma2or', jma2or)
296      WRITE (UNIT=nout, FMT=*) 'jma2or = ', jma2or 
297      !Config Key = jma2oi
298      !Config Desc = number of neighbors of a->o weights (icestreams)
299      !Config Help =
300      !Config Def = 0
301      jma2oi = jpa2o
302      CALL getin ('jma2oi', jma2oi)
303      !Config Key = jmo2a
304      !Config Desc = number of neighbors of o->a weights (temp)
305      !Config Help =
306      !Config Def = 0
307      jmo2a = jpo2a
308      CALL getin ('jmo2a', jmo2a)
309      WRITE (UNIT=nout, FMT=*) 'jmo2a = ', jmo2a 
310      !Config Key = norma2o
311      !Config Desc = type of normalization a->o
312      !Config Help =
313      !Config Def = 0
314      norma2o = 1
315      CALL getin ('norma2o', norma2o)
316      WRITE (UNIT=nout, FMT=*) 'norma2o = ', norma2o
317      !Config Key = normo2a
318      !Config Desc = type of normalization o->a
319      !Config Help =
320      !Config Def = 0
321      normo2a = 1
322      CALL getin ('normo2a', normo2a)
323      WRITE (UNIT=nout, FMT=*) 'normo2a = ', normo2a
324      !!
325      !Config Key = limit_stack
326      !Config Desc = use to limit memory usage in NetCDF
327      !Config Help =
328      !Config Def = n
329      limit_stack = .FALSE.
330      CALL getin ('limit_stack', limit_stack)
331      WRITE (UNIT=nout, FMT=*) 'limit_stack = ', limit_stack 
332      !!
333      !Config Key = l_limit_iosize
334      !COnfig Desc = do not output some diagnostique to limit size of NetCDF files
335      !Config Help =
336      !Config Def = n
337      l_limit_iosize = .FALSE.
338      CALL getin ('l_limit_iosize', l_limit_iosize)
339      WRITE (unit=nout, fmt=*) 'l_limit_iosize = ', l_limit_iosize
340      !Config Key = slice_size
341      !Config Desc = Size of slice in case of limit_stack
342      !Config Help =
343      !Config Def = 10
344      slice_size = 10
345      CALL getin ('slice_size', slice_size)
346      WRITE (UNIT=nout, FMT=*) 'slice_size = ', slice_size
347      !Config Key = c_oasis
348      !Config Desc = define file format for Oasis
349      !Config Help =
350      !Config Def = 2.2
351      c_oasis = '2.2'
352      CALL getin ('c_oasis', c_oasis)
353      WRITE (UNIT=nout, FMT=*) 'c_oasis = ', c_oasis 
354      !Config Key = l_grid_cdf
355      !Config Desc = Use if cdf grid should be produced
356      !Config Help =
357      !Config Def = y
358      l_grid_cdf = .TRUE.
359      CALL getin ('l_grid_cdf', l_grid_cdf)
360      WRITE (UNIT=nout, FMT=*) 'l_grid_cdf = ', l_grid_cdf 
361!-$$      !Config Key = l_wei_cdf
362!-$$      !Config Desc = Use if cdf weights file produced
363!-$$      !Config Help =
364!-$$      !Config Def = y
365!-$$      l_wei_cdf = .TRUE.
366!-$$      CALL getin ('l_wei_cdf', l_wei_cdf)
367!-$$      WRITE (UNIT=nout, FMT=*) 'l_wei_cdf = ', l_wei_cdf
368      !Config Key = l_wei_i4
369      !Config Desc = Use if i4 weights file produced
370      !Config Help =
371      !Config Def = y
372      l_wei_i4 = .TRUE.
373      CALL getin ('l_wei_i4', l_wei_i4)
374      WRITE (UNIT=nout, FMT=*) 'l_wei_i4 = ', l_wei_i4
375      !Config Key = l_wei_i8
376      !Config Desc = Use if I8 weights file produced
377      !Config Help =
378      !Config Def = y
379      l_wei_i8 = .FALSE.
380      CALL getin ('l_wei_i8', l_wei_i8)
381      WRITE (UNIT=nout, FMT=*) 'l_wei_i8 = ', l_wei_i8
382
383      !Config Key = l_wei_oasis_3
384      !Config Desc = Use if OASIS3 weights file produced
385      !Config Help =
386      !Config Def = y
387      l_wei_oasis_3 = .TRUE.
388      CALL getin ('l_wei_oasis_3', l_wei_oasis_3)
389      WRITE (UNIT=nout, FMT=*) 'l_wei_oasis_3 = ', l_wei_oasis_3
390
391      !Config Key = l_wei_oasis_mct
392      !Config Desc = Use if OASIS MCT weights file produced
393      !Config Help =
394      !Config Def = y
395      l_wei_oasis_mct = .TRUE.
396      CALL getin ('l_wei_oasis_mct', l_wei_oasis_mct)
397      WRITE (UNIT=nout, FMT=*) 'l_wei_oasis_mct = ', l_wei_oasis_mct
398     
399      !Config Key = c_read_wei
400      !Config Desc = determined in whihc format weights are read
401      !Config Help =
402      !Config Def = oasis_3
403      CALL getin ('c_read_wei', c_read_wei)
404      WRITE (UNIT=nout, FMT=*) 'c_read_wei = ', TRIM(c_read_wei)
405     
406      !Config Key = c_FlioMode
407      !Config Desc = c_FlioMode = '32', '64', 'REPLACE', 'REP', 'REP64', 'HDF', 'REPHDF'
408      !Config Help =
409      !Config Def = n
410      c_FlioMode = 'REPLACE'
411      CALL getin ('c_FlioMode', c_FlioMode)
412      WRITE (UNIT=nout, FMT=*) 'c_FlioMode = ', c_FlioMode
413      !!
414      !! =======================================
415      !!
416      !! Computed quantities
417      !!
418      jpon  = jpoi * jpoj     ! Global (1D) dimensions for ocean
419      jpan  = jpai * jpaj     ! Global (1D) dimensions for ocean
420      jpanu = jpai * jpaj
421      jpanv = jpai * jpaj
422      !!
423      WRITE (UNIT=nout, FMT=*) 'jpon  = ', jpon 
424      WRITE (UNIT=nout, FMT=*) 'jpan  = ', jpan 
425      WRITE (UNIT=nout, FMT=*) 'jpanu = ', jpanu 
426      WRITE (UNIT=nout, FMT=*) 'jpanv = ', jpanv 
427      !!
428      !Config Key = locerev
429      !Config Desc = Strategie de nommage. Si TRUE: opat.lon, sinon topa.lon
430      !Config Def = n
431      SELECT CASE (TRIM(cotyp))
432      CASE ('orca4')
433         WRITE (unit=nout,fmt=*) 'Case ORCA4 for locerev'
434         locerev = .TRUE. ! Si .TRUE. nom de champs type  opat.lon, sinon topa.lon
435      CASE ('orca2')
436         WRITE (unit=nout,fmt=*) 'Case ORCA2 for locerev'
437         locerev = .TRUE.
438      CASE ('orca2.1')
439         WRITE (unit=nout,fmt=*) 'Case ORCA2 for locerev'
440         locerev = .TRUE.
441      CASE Default
442         WRITE (unit=nout,fmt=*) 'Default case for locerev '
443         locerev = .FALSE.
444      END SELECT
445      CALL getin ('locerev', locerev)
446      WRITE (UNIT=nout, FMT=*) 'locerev = ', locerev
447      !!
448      !Config Key = lriv
449      !Config Desc = Traitement du runoff des rivières avec les embouchures exactes
450      !Config Def = n
451      lriv     = .FALSE. 
452      CALL getin ('lriv', lriv)
453      WRITE (UNIT=nout, FMT=*) 'lriv = ', lriv
454      !Config Key = lcoast
455      !Config Desc = Traitement specifique des points cotiers
456      !Config Def = y
457      lcoast   = .TRUE. 
458      CALL getin ('lcoast', lcoast)
459      WRITE (UNIT=nout, FMT=*) 'lcoast = ', lcoast
460      !Config Key = lint_atm
461      !Config Desc = Calcul pour run-off intégré sur la maille atm
462      !Config Def = y
463      lint_atm = .TRUE.   
464      CALL getin ('lint_atm', lint_atm)
465      WRITE (UNIT=nout, FMT=*) 'lint_atm = ', lint_atm
466      !Config Key = lint_oce
467      !Config Desc = Calcul pour run-off intégré sur la maille oce
468      !Config Def = n
469      CALL getin ('lint_oce', lint_oce)
470      lint_oce = .FALSE. 
471      WRITE (UNIT=nout, FMT=*) 'lint_oce = ', lint_oce
472
473
474
475      !Config Key  = epsfrac
476      !Config Desc = Min fraction of sea acceptable
477      !Config Def  =  1.0E-10_rl
478      !Config Help =
479      epsfrac = 1.0E-10_rl
480      CALL getin ('epsfrac', epsfrac)
481      WRITE (unit=nout, fmt=*) 'epsfrac = ', epsfrac
482     
483      !Config Key = l_etal_oce
484      !Config Desc =  ! On etale sur les point océans  proches
485      !Config Def = n
486      l_etal_oce = .TRUE.
487      CALL getin ('l_etal_oce', l_etal_oce)
488      WRITE (UNIT=nout, FMT=*) 'l_etal_oce = ',l_etal_oce
489
490      !Config Key = dist_etal_oce
491      !Config Desc =  ! On etale sur les point océans  proches
492      !Config Def = 400.0E0
493      l_etal_oce = .TRUE.
494      CALL getin ('dist_etal_oce', dist_etal_oce)
495      WRITE (UNIT=nout, FMT=*) 'dist_etal_oce = ', dist_etal_oce
496     
497      !Config Key = lnear
498      !Config Desc =  Extension de 1 point a l''interieur, vers le point ocean le plus proche'
499      !Config Def = n
500      lnear    = .FALSE. 
501      CALL getin ('lnear', lnear)
502      WRITE (UNIT=nout, FMT=*) 'lnear = ', lnear
503
504      !Config Key = lnei
505      !Config Desc = Extension de 1 point a l''interieur, vers le point atm voisin'
506      !Config Def = n
507      lnei     = .FALSE. 
508      CALL getin ('lnei', lnei)
509      WRITE (UNIT=nout, FMT=*)  'lnei = ', lnei
510
511      !Config Key = ltotal
512      !Config Desc = les point atmosphères mouilles les plus proches.
513      !Config Def = n
514      ltotal = .FALSE.    ! Route tout les point atm vers l'oce le plus proche.
515      CALL getin ('ltotal', ltotal)
516      WRITE (UNIT=nout, FMT=*) 'ltotal = ', ltotal
517      !Config Key = ltotal_dist
518
519      !Config Desc =  ! Route tout les point atm vers l'oce le plus proche, avec distance maxi
520      !Config Def = n
521      ltotal_dist = .FALSE.
522      CALL getin ('ltotal_dist', ltotal_dist)
523      WRITE (UNIT=nout, FMT=*) 'ltotal_dist = ', ltotal_dist
524
525      !Config Key = ltotal_dist_2
526      !Config Desc =  ! Route tout les point atm vers les oce le plus proche, avec distance maxi
527      !               ! On etale sur les point océans cotes proches
528      !Config Def = n
529      ltotal_dist_2 = .TRUE.
530      CALL getin ('ltotal_dist_2', ltotal_dist_2)
531      WRITE (UNIT=nout, FMT=*) 'ltotal_dist_2 = ', ltotal_dist_2
532
533      !Config Key = ltotal_dist_3
534      !Config Desc =  ! Route tout les point atm vers les oce le plus proche, avec distance maxi
535      !               ! On etale sur les point océans proches, cotiers ou pas
536      !Config Def = n
537      ltotal_dist_3 = .TRUE.
538      CALL getin ('ltotal_dist_3', ltotal_dist_3)
539      WRITE (UNIT=nout, FMT=*) 'ltotal_dist_3 = ', ltotal_dist_3
540
541     
542      !Config Key = dist_max
543      !Config Desc = Distance maximale de recherche des voisins océans cotiers
544      !Config Def = 400.0E3
545      dist_max = 400.0E3_rl
546      CALL getin ('dist_max_voisin', dist_max)
547      WRITE (UNIT=nout, FMT=*) 'dist_max = ', dist_max
548
549      !Config Key = dist_max_oce
550      !Config Desc = Distance maximale de recherche des voisins océans
551      !Config Def = 400.0E3
552      dist_max_oce = 400.0E3_rl
553      CALL getin ('dist_max_oce', dist_max_oce)
554      WRITE (UNIT=nout, FMT=*) 'dist_max_oce = ', dist_max_oce
555
556      !Config Key = dist_max_atm
557      !Config Desc = Distance maximale de recherche des voisins atmosphere
558      !Config Def = 400.0E3
559      dist_max_atm = 400.0E3_rl
560      CALL getin ('dist_max_atm', dist_max_atm)
561      WRITE (UNIT=nout, FMT=*) 'dist_max_atm = ', dist_max_atm
562     
563     
564      !Config Key = dist_max_large
565      !Config Desc = Distance maximale de recherche des larges océans, vers le large
566      !Config Def = 400.0E3
567      dist_max_large = 400.0E3_rl
568      CALL getin ('dist_max_large', dist_max_large)
569      WRITE (UNIT=nout, FMT=*) 'dist_max_large = ', dist_max_large
570
571      l_large = .TRUE.
572      CALL getin ( 'l_large', l_large)
573
574      !!
575      !Config Key = lessai
576      !Config Desc = Essai de completion du run-off
577      !Config Def = n
578      lessai = .FALSE.
579      CALL getin ('lessai', lessai)
580      WRITE (UNIT=nout, FMT=*) 'lessai = ', lessai
581
582
583      !Config Key = jp_calv
584      !Config Desc = nombre de bandes pour le calving
585      !Config Def = 3
586      jp_calv = 3
587      CALL getin ('jp_calv', jp_calv)
588      WRITE (nout,*) 'Nombre de bandes : ', jp_calv
589
590      ALLOCATE (ylimits (1:jp_calv+1), STAT=ierr) ; CALL chk_allo (ierr, 'ylimits')
591      !Config Key = ylimits
592      !Config Desc = nombre de bandes pour le calving
593      CALL getin ('ylimits', ylimits)
594      WRITE (nout,*) 'Limites des  bandes : ', ylimits
595
596      !Config Key = l_calving_nomed
597      !Config Desc = Calving does not go to mediterranean seas (includes Red Sea, Persian Gulf)
598      !Config Def = n
599      l_calving_nomed = .FALSE.
600      CALL getin ('l_calving_nomed', l_calving_nomed)
601      WRITE (UNIT=nout, FMT=*) 'l_calving_nomed = ', l_calving_nomed
602     
603      !Config Key = l_calving_noatl
604      !Config Desc = Calving does not go to Atlantic
605      !Config Def = n
606      l_calving_noatl = .FALSE.
607      CALL getin ('l_calving_noatl', l_calving_noatl)
608      WRITE (UNIT=nout, FMT=*) 'l_calving_noatl = ', l_calving_noatl
609
610      !Config Key = l_calving_nopac
611      !Config Desc = Calving does not go to Pacific
612      !Config Def = n
613      l_calving_nopac = .FALSE.
614      CALL getin ('l_calving_nopac', l_calving_nopac)
615      WRITE (UNIT=nout, FMT=*) 'l_calving_nopac = ', l_calving_nopac
616     
617      !Config Key = cotes_omsk
618      !Config Desc = what ocean mask is written in Mosaic MCT file for runoff
619      !Config Def = noperio
620      cotes_omsk='noperio'
621      CALL getin ('cotes_omsk', cotes_omsk)
622      WRITE (UNIT=nout, FMT=*) 'cotes_omsk = ', TRIM(cotes_omsk)
623
624      !Config Key = cotes_amsk
625      !Config Desc = what atm mask is written in Mosaic MCT file for runoff
626      !Config Def = full
627      cotes_amsk='full'
628      CALL getin ('cotes_amsk', cotes_amsk)
629      WRITE (UNIT=nout, FMT=*) 'cotes_amsk = ', TRIM(cotes_amsk)
630
631      c_basins = 'eORCA1.2.nc'
632      CALL getin ( 'c_basins', c_basins)
633      WRITE (UNIT=nout, FMT=*) 'c_basins = ', c_basins
634     
635      cl_atl   = 'mask_atl'
636      CALL getin ('cl_atl', cl_atl )
637      WRITE (UNIT=nout, FMT=*) 'cl_atl = ', cl_atl
638           
639      cl_pac   = 'mask_pac'
640      CALL getin ('cl_pac', cl_pac )
641      WRITE (UNIT=nout, FMT=*) 'cl_pac = ', cl_pac
642           
643      cl_nomed = 'mask_nomed'
644      CALL getin ('cl_nomed', cl_nomed )
645      WRITE (UNIT=nout, FMT=*) 'cl_nomed = ',cl_nomed
646
647      cl_noclo = 'mask_noclose'
648      CALL getin ('cl_noclo', cl_noclo )
649      WRITE (UNIT=nout, FMT=*) 'cl_noclo = ', cl_noclo
650
651
652      CALL getin_dump !! ( 'used' // TRIM(c_suffix))
653      !!
654   END SUBROUTINE inipar
655END MODULE mod_inipar
656
Note: See TracBrowser for help on using the repository browser.