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

Last change on this file since 3326 was 3326, checked in by omamce, 7 years ago

O.M. : Utility to generate interpolatio weights for OASIS-MCT

File size: 21.8 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      !!
140      !! Define atmosphere model
141      !Config Key  = jpai
142      !Config Desc = atm x dimension
143      !Config Help =
144      !Config Def  = 0
145      CALL getin ('jpai', jpai)
146      !Config Key  = jpaj
147      !Config Desc = atm y dimension
148      !Config Help =
149      !Config Def  = 0
150      CALL getin ('jpaj', jpaj)
151      jpait = jpai   ; jpajt = jpaj+1
152      jpaiu = jpai+1 ; jpaju = jpaj+1
153      jpaiv = jpai+1 ; jpajv = jpaj
154
155      jpaj = jpaj+1
156      WRITE (unit=nout, fmt=*) 'jpai  = ', jpai , ' jpaj  = ', jpaj
157      WRITE (unit=nout, fmt=*) 'jpait = ', jpait, ' jpajt = ', jpajt
158      WRITE (unit=nout, fmt=*) 'jpaiu = ', jpaiu, ' jpaju = ', jpaju
159      WRITE (unit=nout, fmt=*) 'jpaiv = ', jpaiv, ' jpajv = ', jpajv
160
161
162      !Config Key  = camod
163      !Config Desc = atm model name
164      !Config Help =
165      !Config Def  = lmd
166      CALL getin ('camod', camod)
167      WRITE (unit=nout, fmt=*) 'comod = ', comod
168      !Config Key  = catyp
169      !Config Desc = atm model type
170      !Config Help =
171      !Config Def  = lmdz
172      catyp = 'lmdz'
173      CALL getin ('catyp', catyp)
174      WRITE (unit=nout, fmt=*) 'catyp = ', catyp
175      !Config Key  = jpae
176      !Config Desc = number of edges for atm
177      !Config Def  = 9
178      !Config Help = Number (maxi) of edges to describe atm box
179      jpae = 9_il
180      CALL getin ('jpae', jpae)
181      WRITE (unit=nout, fmt=*) 'jpae = ', jpae
182      !Config Key  = naperio
183      !Config Desc = atm periodicity type
184      !Config Def  = -1
185      !Config Help = Number (maxi) of edges to describe ocean box
186      naperio = -1_il
187      CALL getin ('naperio', naperio)
188      WRITE (UNIT=nout, FMT=*) 'naperio = ', naperio 
189     
190      !Config Key  = la_nortop
191      !Config Desc = atm latitudes orientation in masks.nc, areas.nc, grids.nc
192      !Config Def  = .TRUE.
193      !Config Help = .TRUE. increasing latitudes
194      la_nortop = .TRUE.
195      CALL getin ('la_nortop', la_nortop)
196      WRITE (unit=nout, fmt=*) 'la_nortop = ', la_nortop
197
198      !Config Key  = l_recalc_a
199      !Config Desc = Recompute atm surfaces
200      !Config Def  = y
201      !Config Help = Recompute atm surfaces
202      l_recalc_a = .TRUE.
203      CALL getin ('l_recalc_a', l_recalc_a)
204      WRITE (unit=nout, fmt=*) 'l_recalc_a = ', l_recalc_a
205     
206      !Config Key  = la_pole
207      !Config Desc special handing of atm pole point
208      !Config Def  = y
209      la_pole = .FALSE.
210      CALL getin ( 'la_pole', la_pole)
211      WRITE (unit=nout, fmt=*) 'la_pole = ', la_pole
212
213      !Config Key = o2a_orien
214      !Config Desc  = orientation for o2a diag file
215      !Config Def  = nord_en_haut
216      o2a_orien = "nord_en_haut"
217      CALL getin ( 'o2a_orien', o2a_orien)
218      WRITE (unit=nout, fmt=*) 'o2a_orien = ', TRIM(o2a_orien)
219
220      !Config Key  = lmaska
221      !Config Desc = If TRUE, masked points of atmospheric grid (land) are considered for computing.
222      !Config Def  = y
223      lmaska = .TRUE.
224      CALL getin ( 'lmaska', lmaska)
225      WRITE (unit=nout, fmt=*) 'lmaska = ', lmaska
226     
227      !Config Key  = lmasko
228      !Config Desc = If TRUE, masked points of ocean grid (land) are considered for computing.
229      !Config Def  = n
230      lmasko = .FALSE.
231      CALL getin ( 'lmasko', lmasko)
232      WRITE (unit=nout, fmt=*) 'lmasko = ', lmasko
233     
234      !Config Key  = lwro2a
235      !Config Desc = TRUE if oce -> atm weights/adresses are computed
236      !Config Def  = y
237      lwro2a = .TRUE.
238      CALL getin ( 'lwro2a', lwro2a)
239      WRITE (unit=nout, fmt=*) 'lwro2a = ', lwro2a
240
241      !Config Key  = lwra2o
242      !Config Desc = TRUE if atm -> oce weights/adresses are computed
243      !Config Def  = y
244      lwra2o = .TRUE.
245      CALL getin ( 'lwra2o', lwra2o)
246      WRITE (unit=nout, fmt=*) 'lwra2o = ', lwra2o
247     
248      !Config Key  = normo2a
249      !Config Desc = Type of normalization oce -> atm: 0: none, 1: intensive, 2: extensive
250      !Config Def  = 1
251      normo2a = 1
252      CALL getin ( 'normo2a', normo2a)
253      WRITE (unit=nout, fmt=*) 'normo2a = ', normo2a
254
255      !Config Key  = norma2o
256      !Config Desc = Type of normalization atm->oce : 0: none, 1: intensive, 2: extensive
257      !Config Def  = 1
258      norma2o = 1
259      CALL getin ( 'norma2o', norma2o)
260      WRITE (unit=nout, fmt=*) 'norma2o = ', norma2o
261
262!!!
263      !Config Key = jpa2o
264      !Config Desc = max number of neighbors of a->o weights
265      !Config Help =
266      !Config Def = 0
267      CALL getin ('jpa2o', jpa2o)
268      WRITE (UNIT=nout, FMT=*) 'jpa2o = ', jpa2O 
269      !Config Key = jpo2a
270      !Config Desc = max number of neighbors of o-> weights
271      !Config Help =
272      !Config Def = 0
273      CALL getin ('jpo2a', jpo2a)
274      WRITE (UNIT=nout, FMT=*) 'jpo2a = ', jpo2a 
275      !!
276      !Config Key = jma2o
277      !Config Desc = number of neighbors of a->o weights (fluxes)
278      !Config Help =
279      !Config Def = 0
280      jma2o = jpa2o
281      CALL getin ('jma2o', jma2o)
282      WRITE (UNIT=nout, FMT=*) 'jma2o = ', jma2o 
283      !Config Key = jma2or
284      !Config Desc = number of neighbors of a->o weights (runoff)
285      !Config Help =
286      !Config Def = 0
287      jma2or = jpa2o
288      CALL getin ('jma2or', jma2or)
289      WRITE (UNIT=nout, FMT=*) 'jma2or = ', jma2or 
290      !Config Key = jma2oi
291      !Config Desc = number of neighbors of a->o weights (icestreams)
292      !Config Help =
293      !Config Def = 0
294      jma2oi = jpa2o
295      CALL getin ('jma2oi', jma2oi)
296      !Config Key = jmo2a
297      !Config Desc = number of neighbors of o->a weights (temp)
298      !Config Help =
299      !Config Def = 0
300      jmo2a = jpo2a
301      CALL getin ('jmo2a', jmo2a)
302      WRITE (UNIT=nout, FMT=*) 'jmo2a = ', jmo2a 
303      !Config Key = norma2o
304      !Config Desc = type of normalization a->o
305      !Config Help =
306      !Config Def = 0
307      norma2o = 1
308      CALL getin ('norma2o', norma2o)
309      WRITE (UNIT=nout, FMT=*) 'norma2o = ', norma2o
310      !Config Key = normo2a
311      !Config Desc = type of normalization o->a
312      !Config Help =
313      !Config Def = 0
314      normo2a = 1
315      CALL getin ('normo2a', normo2a)
316      WRITE (UNIT=nout, FMT=*) 'normo2a = ', normo2a
317      !!
318      !Config Key = limit_stack
319      !Config Desc = use to limit memory usage in NetCDF
320      !Config Help =
321      !Config Def = n
322      limit_stack = .FALSE.
323      CALL getin ('limit_stack', limit_stack)
324      WRITE (UNIT=nout, FMT=*) 'limit_stack = ', limit_stack 
325      !!
326      !Config Key = l_limit_iosize
327      !COnfig Desc = do not output some diagnostique to limit size of NetCDF files
328      !Config Help =
329      !Config Def = n
330      l_limit_iosize = .FALSE.
331      CALL getin ('l_limit_iosize', l_limit_iosize)
332      WRITE (unit=nout, fmt=*) 'l_limit_iosize = ', l_limit_iosize
333      !Config Key = slice_size
334      !Config Desc = Size of slice in case of limit_stack
335      !Config Help =
336      !Config Def = 10
337      slice_size = 10
338      CALL getin ('slice_size', slice_size)
339      WRITE (UNIT=nout, FMT=*) 'slice_size = ', slice_size
340      !Config Key = c_oasis
341      !Config Desc = define file format for Oasis
342      !Config Help =
343      !Config Def = 2.2
344      c_oasis = '2.2'
345      CALL getin ('c_oasis', c_oasis)
346      WRITE (UNIT=nout, FMT=*) 'c_oasis = ', c_oasis 
347      !Config Key = l_grid_cdf
348      !Config Desc = Use if cdf grid should be produced
349      !Config Help =
350      !Config Def = y
351      l_grid_cdf = .TRUE.
352      CALL getin ('l_grid_cdf', l_grid_cdf)
353      WRITE (UNIT=nout, FMT=*) 'l_grid_cdf = ', l_grid_cdf 
354!-$$      !Config Key = l_wei_cdf
355!-$$      !Config Desc = Use if cdf weights file produced
356!-$$      !Config Help =
357!-$$      !Config Def = y
358!-$$      l_wei_cdf = .TRUE.
359!-$$      CALL getin ('l_wei_cdf', l_wei_cdf)
360!-$$      WRITE (UNIT=nout, FMT=*) 'l_wei_cdf = ', l_wei_cdf
361      !Config Key = l_wei_i4
362      !Config Desc = Use if i4 weights file produced
363      !Config Help =
364      !Config Def = y
365      l_wei_i4 = .TRUE.
366      CALL getin ('l_wei_i4', l_wei_i4)
367      WRITE (UNIT=nout, FMT=*) 'l_wei_i4 = ', l_wei_i4
368      !Config Key = l_wei_i8
369      !Config Desc = Use if I8 weights file produced
370      !Config Help =
371      !Config Def = y
372      l_wei_i8 = .FALSE.
373      CALL getin ('l_wei_i8', l_wei_i8)
374      WRITE (UNIT=nout, FMT=*) 'l_wei_i8 = ', l_wei_i8
375
376      !Config Key = l_wei_oasis_3
377      !Config Desc = Use if OASIS3 weights file produced
378      !Config Help =
379      !Config Def = y
380      l_wei_oasis_3 = .TRUE.
381      CALL getin ('l_wei_oasis_3', l_wei_oasis_3)
382      WRITE (UNIT=nout, FMT=*) 'l_wei_oasis_3 = ', l_wei_oasis_3
383
384      !Config Key = l_wei_oasis_mct
385      !Config Desc = Use if OASIS MCT weights file produced
386      !Config Help =
387      !Config Def = y
388      l_wei_oasis_mct = .TRUE.
389      CALL getin ('l_wei_oasis_mct', l_wei_oasis_mct)
390      WRITE (UNIT=nout, FMT=*) 'l_wei_oasis_mct = ', l_wei_oasis_mct
391     
392      !Config Key = c_read_wei
393      !Config Desc = determined in whihc format weights are read
394      !Config Help =
395      !Config Def = oasis_3
396      CALL getin ('c_read_wei', c_read_wei)
397      WRITE (UNIT=nout, FMT=*) 'c_read_wei = ', TRIM(c_read_wei)
398     
399      !Config Key = c_FlioMode
400      !Config Desc = c_FlioMode = '32', '64', 'REPLACE', 'REP', 'REP64', 'HDF', 'REPHDF'
401      !Config Help =
402      !Config Def = n
403      c_FlioMode = 'REPLACE'
404      CALL getin ('c_FlioMode', c_FlioMode)
405      WRITE (UNIT=nout, FMT=*) 'c_FlioMode = ', c_FlioMode
406      !!
407      !! =======================================
408      !!
409      !! Computed quantities
410      !!
411      jpon  = jpoi * jpoj     ! Global (1D) dimensions for ocean
412      jpan  = jpai * jpaj     ! Global (1D) dimensions for ocean
413      jpanu = jpai * jpaj
414      jpanv = jpai * jpaj
415      !!
416      WRITE (UNIT=nout, FMT=*) 'jpon  = ', jpon 
417      WRITE (UNIT=nout, FMT=*) 'jpan  = ', jpan 
418      WRITE (UNIT=nout, FMT=*) 'jpanu = ', jpanu 
419      WRITE (UNIT=nout, FMT=*) 'jpanv = ', jpanv 
420      !!
421      !Config Key = locerev
422      !Config Desc = Strategie de nommage. Si TRUE: opat.lon, sinon topa.lon
423      !Config Def = n
424      SELECT CASE (TRIM(cotyp))
425      CASE ('orca4')
426         WRITE (unit=nout,fmt=*) 'Case ORCA4 for locerev'
427         locerev = .TRUE. ! Si .TRUE. nom de champs type  opat.lon, sinon topa.lon
428      CASE ('orca2')
429         WRITE (unit=nout,fmt=*) 'Case ORCA2 for locerev'
430         locerev = .TRUE.
431      CASE ('orca2.1')
432         WRITE (unit=nout,fmt=*) 'Case ORCA2 for locerev'
433         locerev = .TRUE.
434      CASE Default
435         WRITE (unit=nout,fmt=*) 'Default case for locerev '
436         locerev = .FALSE.
437      END SELECT
438      CALL getin ('locerev', locerev)
439      WRITE (UNIT=nout, FMT=*) 'locerev = ', locerev
440      !!
441      !Config Key = lriv
442      !Config Desc = Traitement du runoff des rivières avec les embouchures exactes
443      !Config Def = n
444      lriv     = .FALSE. 
445      CALL getin ('lriv', lriv)
446      WRITE (UNIT=nout, FMT=*) 'lriv = ', lriv
447      !Config Key = lcoast
448      !Config Desc = Traitement specifique des points cotiers
449      !Config Def = y
450      lcoast   = .TRUE. 
451      CALL getin ('lcoast', lcoast)
452      WRITE (UNIT=nout, FMT=*) 'lcoast = ', lcoast
453      !Config Key = lint_atm
454      !Config Desc = Calcul pour run-off intégré sur la maille atm
455      !Config Def = y
456      lint_atm = .TRUE.   
457      CALL getin ('lint_atm', lint_atm)
458      WRITE (UNIT=nout, FMT=*) 'lint_atm = ', lint_atm
459      !Config Key = lint_oce
460      !Config Desc = Calcul pour run-off intégré sur la maille oce
461      !Config Def = n
462      CALL getin ('lint_oce', lint_oce)
463      lint_oce = .FALSE. 
464      WRITE (UNIT=nout, FMT=*) 'lint_oce = ', lint_oce
465
466
467      !Config Key = l_etal_oce
468      !Config Desc =  ! On etale sur les point océans  proches
469      !Config Def = n
470      l_etal_oce = .TRUE.
471      CALL getin ('l_etal_oce', l_etal_oce)
472      WRITE (UNIT=nout, FMT=*) 'l_etal_oce = ',l_etal_oce
473
474      !Config Key = dist_etal_oce
475      !Config Desc =  ! On etale sur les point océans  proches
476      !Config Def = 400.0E0
477      l_etal_oce = .TRUE.
478      CALL getin ('dist_etal_oce', dist_etal_oce)
479      WRITE (UNIT=nout, FMT=*) 'dist_etal_oce = ', dist_etal_oce
480     
481      !Config Key = lnear
482      !Config Desc =  Extension de 1 point a l''interieur, vers le point ocean le plus proche'
483      !Config Def = n
484      lnear    = .FALSE. 
485      CALL getin ('lnear', lnear)
486      WRITE (UNIT=nout, FMT=*) 'lnear = ', lnear
487
488      !Config Key = lnei
489      !Config Desc = Extension de 1 point a l''interieur, vers le point atm voisin'
490      !Config Def = n
491      lnei     = .FALSE. 
492      CALL getin ('lnei', lnei)
493      WRITE (UNIT=nout, FMT=*)  'lnei = ', lnei
494
495      !Config Key = ltotal
496      !Config Desc = les point atmosphères mouilles les plus proches.
497      !Config Def = n
498      ltotal = .FALSE.    ! Route tout les point atm vers l'oce le plus proche.
499      CALL getin ('ltotal', ltotal)
500      WRITE (UNIT=nout, FMT=*) 'ltotal = ', ltotal
501      !Config Key = ltotal_dist
502
503      !Config Desc =  ! Route tout les point atm vers l'oce le plus proche, avec distance maxi
504      !Config Def = n
505      ltotal_dist = .FALSE.
506      CALL getin ('ltotal_dist', ltotal_dist)
507      WRITE (UNIT=nout, FMT=*) 'ltotal_dist = ', ltotal_dist
508
509      !Config Key = ltotal_dist_2
510      !Config Desc =  ! Route tout les point atm vers les oce le plus proche, avec distance maxi
511      !               ! On etale sur les point océans cotes proches
512      !Config Def = n
513      ltotal_dist_2 = .TRUE.
514      CALL getin ('ltotal_dist_2', ltotal_dist_2)
515      WRITE (UNIT=nout, FMT=*) 'ltotal_dist_2 = ', ltotal_dist_2
516
517      !Config Key = ltotal_dist_3
518      !Config Desc =  ! Route tout les point atm vers les oce le plus proche, avec distance maxi
519      !               ! On etale sur les point océans proches, cotiers ou pas
520      !Config Def = n
521      ltotal_dist_3 = .TRUE.
522      CALL getin ('ltotal_dist_3', ltotal_dist_3)
523      WRITE (UNIT=nout, FMT=*) 'ltotal_dist_3 = ', ltotal_dist_3
524
525     
526      !Config Key = dist_max
527      !Config Desc = Distance maximale de recherche des voisins océans cotiers
528      !Config Def = 400.0E3
529      dist_max = 400.0E3_rl
530      CALL getin ('dist_max_voisin', dist_max)
531      WRITE (UNIT=nout, FMT=*) 'dist_max = ', dist_max
532
533      !Config Key = dist_max_oce
534      !Config Desc = Distance maximale de recherche des voisins océans
535      !Config Def = 400.0E3
536      dist_max_oce = 400.0E3_rl
537      CALL getin ('dist_max_oce', dist_max_oce)
538      WRITE (UNIT=nout, FMT=*) 'dist_max_oce = ', dist_max_oce
539
540      !Config Key = dist_max_atm
541      !Config Desc = Distance maximale de recherche des voisins atmosphere
542      !Config Def = 400.0E3
543      dist_max_atm = 400.0E3_rl
544      CALL getin ('dist_max_atm', dist_max_atm)
545      WRITE (UNIT=nout, FMT=*) 'dist_max_atm = ', dist_max_atm
546     
547     
548      !Config Key = dist_max_large
549      !Config Desc = Distance maximale de recherche des larges océans, vers le large
550      !Config Def = 400.0E3
551      dist_max_large = 400.0E3_rl
552      CALL getin ('dist_max_large', dist_max_large)
553      WRITE (UNIT=nout, FMT=*) 'dist_max_large = ', dist_max_large
554
555      l_large = .TRUE.
556      CALL getin ( 'l_large', l_large)
557
558      !!
559      !Config Key = lessai
560      !Config Desc = Essai de completion du run-off
561      !Config Def = n
562      lessai = .FALSE.
563      CALL getin ('lessai', lessai)
564      WRITE (UNIT=nout, FMT=*) 'lessai = ', lessai
565
566
567      !Config Key = jp_calv
568      !Config Desc = nombre de bandes pour le calving
569      !Config Def = 3
570      jp_calv = 3
571      CALL getin ('jp_calv', jp_calv)
572      WRITE (nout,*) 'Nombre de bandes : ', jp_calv
573
574      ALLOCATE (ylimits (1:jp_calv+1), STAT=ierr) ; CALL chk_allo (ierr, 'ylimits')
575      !Config Key = ylimits
576      !Config Desc = nombre de bandes pour le calving
577      CALL getin ('ylimits', ylimits)
578      WRITE (nout,*) 'Limites des  bandes : ', ylimits
579
580      !Config Key = l_calving_nomed
581      !Config Desc = Calving does not go to mediterranean seas (includes Red Sea, Persian Gulf)
582      !Config Def = n
583      l_calving_nomed = .FALSE.
584      CALL getin ('l_calving_nomed', l_calving_nomed)
585      WRITE (UNIT=nout, FMT=*) 'l_calving_nomed = ', l_calving_nomed
586     
587      !Config Key = l_calving_noatl
588      !Config Desc = Calving does not go to Atlantic
589      !Config Def = n
590      l_calving_noatl = .FALSE.
591      CALL getin ('l_calving_noatl', l_calving_noatl)
592      WRITE (UNIT=nout, FMT=*) 'l_calving_noatl = ', l_calving_noatl
593
594      !Config Key = l_calving_nopac
595      !Config Desc = Calving does not go to Pacific
596      !Config Def = n
597      l_calving_nopac = .FALSE.
598      CALL getin ('l_calving_nopac', l_calving_nopac)
599      WRITE (UNIT=nout, FMT=*) 'l_calving_nopac = ', l_calving_nopac
600     
601      !Config Key = cotes_omsk
602      !Config Desc = what ocean mask is written in Mosaic MCT file for runoff
603      !Config Def = noperio
604      cotes_omsk='noperio'
605      CALL getin ('cotes_omsk', cotes_omsk)
606      WRITE (UNIT=nout, FMT=*) 'cotes_omsk = ', TRIM(cotes_omsk)
607
608      !Config Key = cotes_amsk
609      !Config Desc = what atm mask is written in Mosaic MCT file for runoff
610      !Config Def = full
611      cotes_amsk='full'
612      CALL getin ('cotes_amsk', cotes_amsk)
613      WRITE (UNIT=nout, FMT=*) 'cotes_amsk = ', TRIM(cotes_amsk)
614
615      c_basins = 'eORCA1.2.nc'
616      CALL getin ( 'c_basins', c_basins)
617      WRITE (UNIT=nout, FMT=*) 'c_basins = ', c_basins
618     
619      cl_atl   = 'mask_atl'
620      CALL getin ('cl_atl', cl_atl )
621      WRITE (UNIT=nout, FMT=*) 'cl_atl = ', cl_atl
622           
623      cl_pac   = 'mask_pac'
624      CALL getin ('cl_pac', cl_pac )
625      WRITE (UNIT=nout, FMT=*) 'cl_pac = ', cl_pac
626           
627      cl_nomed = 'mask_nomed'
628      CALL getin ('cl_nomed', cl_nomed )
629      WRITE (UNIT=nout, FMT=*) 'cl_nomed = ',cl_nomed
630
631      cl_noclo = 'mask_noclose'
632      CALL getin ('cl_noclo', cl_noclo )
633      WRITE (UNIT=nout, FMT=*) 'cl_noclo = ', cl_noclo
634
635
636      CALL getin_dump !! ( 'used' // TRIM(c_suffix))
637      !!
638   END SUBROUTINE inipar
639END MODULE mod_inipar
640
Note: See TracBrowser for help on using the repository browser.