GCC Code Coverage Report


Directory: ./
File: dyn/conf_gcm.f90
Date: 2022-01-11 19:19:34
Exec Total Coverage
Lines: 184 332 55.4%
Branches: 6 56 10.7%

Line Branch Exec Source
1
2 ! $Id: conf_gcm.F90 3865 2021-03-23 15:14:07Z lmdz-users $
3
4 50 SUBROUTINE conf_gcm( tapedef, etatinit )
5
6 USE control_mod
7 use IOIPSL
8 USE infotrac, ONLY : type_trac
9 use assert_m, only: assert
10 USE comconst_mod, ONLY: dissip_deltaz, dissip_factz, dissip_zref, &
11 iflag_top_bound, mode_top_bound, tau_top_bound, &
12 ngroup
13 USE logic_mod, ONLY: fxyhypb, iflag_phys, ok_etat0, ok_gradsfile, &
14 ok_guide, ok_limit, ok_strato, purmats, read_start, &
15 ysinus, read_orop
16 USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy, &
17 alphax,alphay,taux,tauy
18 USE temps_mod, ONLY: calend, year_len
19
20 IMPLICIT NONE
21 !-----------------------------------------------------------------------
22 ! Auteurs : L. Fairhead , P. Le Van .
23
24 ! Arguments :
25
26 ! tapedef :
27 ! etatinit : = TRUE , on ne compare pas les valeurs des para-
28 ! -metres du zoom avec celles lues sur le fichier start .
29
30 LOGICAL,INTENT(IN) :: etatinit
31 INTEGER,INTENT(IN) :: tapedef
32
33 ! Declarations :
34 ! --------------
35 include "dimensions.h"
36 include "paramet.h"
37 include "comdissnew.h"
38 include "iniprint.h"
39
40 ! local:
41 ! ------
42
43 REAL clonn,clatt,grossismxx,grossismyy
44 REAL dzoomxx,dzoomyy, tauxx,tauyy
45 LOGICAL fxyhypbb, ysinuss
46
47 ! -------------------------------------------------------------------
48
49 ! ......... Version du 29/04/97 ..........
50
51 ! Nouveaux parametres nitergdiv,nitergrot,niterh,tetagdiv,tetagrot,
52 ! tetatemp ajoutes pour la dissipation .
53
54 ! Autre parametre ajoute en fin de liste de tapedef : ** fxyhypb **
55
56 ! Si fxyhypb = .TRUE. , choix de la fonction a derivee tangente hyperb.
57 ! Sinon , choix de fxynew , a derivee sinusoidale ..
58
59 ! ...... etatinit = . TRUE. si defrun est appele dans ETAT0_LMD ou
60 ! LIMIT_LMD pour l'initialisation de start.dat (dic) et
61 ! de limit.dat ( dic) ...........
62 ! Sinon etatinit = . FALSE .
63
64 ! Donc etatinit = .F. si on veut comparer les valeurs de grossismx ,
65 ! grossismy,clon,clat, fxyhypb lues sur le fichier start avec
66 ! celles passees par run.def , au debut du gcm, apres l'appel a
67 ! lectba .
68 ! Ces parmetres definissant entre autres la grille et doivent etre
69 ! pareils et coherents , sinon il y aura divergence du gcm .
70
71 !-----------------------------------------------------------------------
72 ! initialisations:
73 ! ----------------
74
75 !Config Key = lunout
76 !Config Desc = unite de fichier pour les impressions
77 !Config Def = 6
78 !Config Help = unite de fichier pour les impressions
79 !Config (defaut sortie standard = 6)
80 1 lunout=6
81 1 CALL getin('lunout', lunout)
82
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (lunout /= 5 .and. lunout /= 6) THEN
83 OPEN(UNIT=lunout,FILE='lmdz.out',ACTION='write', &
84 STATUS='unknown',FORM='formatted')
85 ENDIF
86
87 !Config Key = prt_level
88 !Config Desc = niveau d'impressions de d\'ebogage
89 !Config Def = 0
90 !Config Help = Niveau d'impression pour le d\'ebogage
91 !Config (0 = minimum d'impression)
92 1 prt_level = 0
93 1 CALL getin('prt_level',prt_level)
94
95 !-----------------------------------------------------------------------
96 ! Parametres de controle du run:
97 !-----------------------------------------------------------------------
98 !Config Key = planet_type
99 !Config Desc = planet type ("earth", "mars", "venus", ...)
100 !Config Def = earth
101 !Config Help = this flag sets the type of atymosphere that is considered
102 1 planet_type="earth"
103 1 CALL getin('planet_type',planet_type)
104
105 !Config Key = calend
106 !Config Desc = type de calendrier utilise
107 !Config Def = earth_360d
108 !Config Help = valeur possible: earth_360d, earth_365d, earth_366d
109 !Config
110 1 calend = 'earth_360d'
111 1 CALL getin('calend', calend)
112 ! initialize year_len for aquaplanets and 1D
113
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 if (calend == 'earth_360d') then
114 1 year_len=360
115 else if (calend == 'earth_365d') then
116 year_len=365
117 else if (calend == 'earth_366d') then
118 year_len=366
119 else
120 year_len=1
121 endif
122
123 !Config Key = dayref
124 !Config Desc = Jour de l'etat initial
125 !Config Def = 1
126 !Config Help = Jour de l'etat initial ( = 350 si 20 Decembre ,
127 !Config par expl. ,comme ici ) ... A completer
128 1 dayref=1
129 1 CALL getin('dayref', dayref)
130
131 !Config Key = anneeref
132 !Config Desc = Annee de l'etat initial
133 !Config Def = 1998
134 !Config Help = Annee de l'etat initial
135 !Config ( avec 4 chiffres ) ... A completer
136 1 anneeref = 1998
137 1 CALL getin('anneeref',anneeref)
138
139 !Config Key = raz_date
140 !Config Desc = Remise a zero de la date initiale
141 !Config Def = 0 (pas de remise a zero)
142 !Config Help = Remise a zero de la date initiale
143 !Config 0 pas de remise a zero, on garde la date du fichier restart
144 !Config 1 prise en compte de la date de gcm.def avec remise a zero
145 !Config des compteurs de pas de temps
146 1 raz_date = 0
147 1 CALL getin('raz_date', raz_date)
148
149 !Config Key = resetvarc
150 !Config Desc = Reinit des variables de controle
151 !Config Def = n
152 !Config Help = Reinit des variables de controle
153 1 resetvarc = .false.
154 1 CALL getin('resetvarc',resetvarc)
155
156 !Config Key = nday
157 !Config Desc = Nombre de jours d'integration
158 !Config Def = 10
159 !Config Help = Nombre de jours d'integration
160 !Config ... On pourait aussi permettre des mois ou des annees !
161 1 nday = 10
162 1 CALL getin('nday',nday)
163
164 !Config Key = starttime
165 !Config Desc = Heure de depart de la simulation
166 !Config Def = 0
167 !Config Help = Heure de depart de la simulation
168 !Config en jour
169 1 starttime = 0
170 1 CALL getin('starttime',starttime)
171
172 !Config Key = day_step
173 !Config Desc = nombre de pas par jour
174 !Config Def = 240
175 !Config Help = nombre de pas par jour (multiple de iperiod) (
176 !Config ici pour dt = 1 min )
177 1 day_step = 240
178 1 CALL getin('day_step',day_step)
179
180 !Config Key = nsplit_phys
181 1 nsplit_phys = 1
182 1 CALL getin('nsplit_phys',nsplit_phys)
183
184 !Config Key = iperiod
185 !Config Desc = periode pour le pas Matsuno
186 !Config Def = 5
187 !Config Help = periode pour le pas Matsuno (en pas de temps)
188 1 iperiod = 5
189 1 CALL getin('iperiod',iperiod)
190
191 !Config Key = iapp_tracvl
192 !Config Desc = frequence du groupement des flux
193 !Config Def = iperiod
194 !Config Help = frequence du groupement des flux (en pas de temps)
195 1 iapp_tracvl = iperiod
196 1 CALL getin('iapp_tracvl',iapp_tracvl)
197
198 !Config Key = iconser
199 !Config Desc = periode de sortie des variables de controle
200 !Config Def = 240
201 !Config Help = periode de sortie des variables de controle
202 !Config (En pas de temps)
203 1 iconser = 240
204 1 CALL getin('iconser', iconser)
205
206 !Config Key = iecri
207 !Config Desc = periode d'ecriture du fichier histoire
208 !Config Def = 1
209 !Config Help = periode d'ecriture du fichier histoire (en jour)
210 1 iecri = 1
211 1 CALL getin('iecri',iecri)
212
213 !Config Key = periodav
214 !Config Desc = periode de stockage fichier histmoy
215 !Config Def = 1
216 !Config Help = periode de stockage fichier histmoy (en jour)
217 1 periodav = 1.
218 1 CALL getin('periodav',periodav)
219
220 !Config Key = output_grads_dyn
221 !Config Desc = output dynamics diagnostics in 'dyn.dat' file
222 !Config Def = n
223 !Config Help = output dynamics diagnostics in Grads-readable 'dyn.dat' file
224 1 output_grads_dyn=.false.
225 1 CALL getin('output_grads_dyn',output_grads_dyn)
226
227 !Config Key = dissip_period
228 !Config Desc = periode de la dissipation
229 !Config Def = 0
230 !Config Help = periode de la dissipation
231 !Config dissip_period=0 => la valeur sera calcule dans inidissip
232 !Config dissip_period>0 => on prend cette valeur
233 1 dissip_period = 0
234 1 CALL getin('dissip_period',dissip_period)
235
236 !cc .... P. Le Van , modif le 29/04/97 .pour la dissipation ...
237 !cc
238
239 !Config Key = lstardis
240 !Config Desc = choix de l'operateur de dissipation
241 !Config Def = y
242 !Config Help = choix de l'operateur de dissipation
243 !Config 'y' si on veut star et 'n' si on veut non-start !
244 !Config Moi y en a pas comprendre !
245 1 lstardis = .TRUE.
246 1 CALL getin('lstardis',lstardis)
247
248 !Config Key = nitergdiv
249 !Config Desc = Nombre d'iteration de gradiv
250 !Config Def = 1
251 !Config Help = nombre d'iterations de l'operateur de dissipation
252 !Config gradiv
253 1 nitergdiv = 1
254 1 CALL getin('nitergdiv',nitergdiv)
255
256 !Config Key = nitergrot
257 !Config Desc = nombre d'iterations de nxgradrot
258 !Config Def = 2
259 !Config Help = nombre d'iterations de l'operateur de dissipation
260 !Config nxgradrot
261 1 nitergrot = 2
262 1 CALL getin('nitergrot',nitergrot)
263
264 !Config Key = niterh
265 !Config Desc = nombre d'iterations de divgrad
266 !Config Def = 2
267 !Config Help = nombre d'iterations de l'operateur de dissipation
268 !Config divgrad
269 1 niterh = 2
270 1 CALL getin('niterh',niterh)
271
272 !Config Key = tetagdiv
273 !Config Desc = temps de dissipation pour div
274 !Config Def = 7200
275 !Config Help = temps de dissipation des plus petites longeur
276 !Config d'ondes pour u,v (gradiv)
277 1 tetagdiv = 7200.
278 1 CALL getin('tetagdiv',tetagdiv)
279
280 !Config Key = tetagrot
281 !Config Desc = temps de dissipation pour grad
282 !Config Def = 7200
283 !Config Help = temps de dissipation des plus petites longeur
284 !Config d'ondes pour u,v (nxgradrot)
285 1 tetagrot = 7200.
286 1 CALL getin('tetagrot',tetagrot)
287
288 !Config Key = tetatemp
289 !Config Desc = temps de dissipation pour h
290 !Config Def = 7200
291 !Config Help = temps de dissipation des plus petites longeur
292 !Config d'ondes pour h (divgrad)
293 1 tetatemp = 7200.
294 1 CALL getin('tetatemp',tetatemp )
295
296 ! Parametres controlant la variation sur la verticale des constantes de
297 ! dissipation.
298 ! Pour le moment actifs uniquement dans la version a 39 niveaux
299 ! avec ok_strato=y
300
301 1 dissip_factz=4.
302 1 dissip_deltaz=10.
303 1 dissip_zref=30.
304 1 CALL getin('dissip_factz',dissip_factz )
305 1 CALL getin('dissip_deltaz',dissip_deltaz )
306 1 CALL getin('dissip_zref',dissip_zref )
307
308 ! ngroup
309 1 ngroup=3
310 1 CALL getin('ngroup',ngroup)
311
312
313 ! top_bound sponge: only active if ok_strato=.true. and iflag_top_bound!=0
314 ! iflag_top_bound=0 for no sponge
315 ! iflag_top_bound=1 for sponge over 4 topmost layers
316 ! iflag_top_bound=2 for sponge from top to ~1% of top layer pressure
317 1 iflag_top_bound=1
318 1 CALL getin('iflag_top_bound',iflag_top_bound)
319
320 ! mode_top_bound : fields towards which sponge relaxation will be done:
321 ! mode_top_bound=0: no relaxation
322 ! mode_top_bound=1: u and v relax towards 0
323 ! mode_top_bound=2: u and v relax towards their zonal mean
324 ! mode_top_bound=3: u,v and pot. temp. relax towards their zonal mean
325 1 mode_top_bound=3
326 1 CALL getin('mode_top_bound',mode_top_bound)
327
328 ! top_bound sponge : inverse of charactericstic relaxation time scale for sponge
329 1 tau_top_bound=1.e-5
330 1 CALL getin('tau_top_bound',tau_top_bound)
331
332 !Config Key = coefdis
333 !Config Desc = coefficient pour gamdissip
334 !Config Def = 0
335 !Config Help = coefficient pour gamdissip
336 1 coefdis = 0.
337 1 CALL getin('coefdis',coefdis)
338
339 !Config Key = purmats
340 !Config Desc = Schema d'integration
341 !Config Def = n
342 !Config Help = Choix du schema d'integration temporel.
343 !Config y = pure Matsuno sinon c'est du Matsuno-leapfrog
344 1 purmats = .FALSE.
345 1 CALL getin('purmats',purmats)
346
347 !Config Key = ok_guide
348 !Config Desc = Guidage
349 !Config Def = n
350 !Config Help = Guidage
351 1 ok_guide = .FALSE.
352 1 CALL getin('ok_guide',ok_guide)
353
354 !Config Key = read_start
355 !Config Desc = Initialize model using a 'start.nc' file
356 !Config Def = y
357 !Config Help = y: intialize dynamical fields using a 'start.nc' file
358 ! n: fields are initialized by 'iniacademic' routine
359 1 read_start= .true.
360 1 CALL getin('read_start',read_start)
361
362 !Config Key = iflag_phys
363 !Config Desc = Avec ls physique
364 !Config Def = 1
365 !Config Help = Permet de faire tourner le modele sans
366 !Config physique.
367 1 iflag_phys = 1
368 1 CALL getin('iflag_phys',iflag_phys)
369
370 !Config Key = iphysiq
371 !Config Desc = Periode de la physique
372 !Config Def = 5
373 !Config Help = Periode de la physique en pas de temps de la dynamique.
374 1 iphysiq = 5
375 1 CALL getin('iphysiq', iphysiq)
376
377 !Config Key = ip_ebil_dyn
378 !Config Desc = PRINT level for energy conserv. diag.
379 !Config Def = 0
380 !Config Help = PRINT level for energy conservation diag. ;
381 ! les options suivantes existent :
382 !Config 0 pas de print
383 !Config 1 pas de print
384 !Config 2 print,
385 1 ip_ebil_dyn = 0
386 1 CALL getin('ip_ebil_dyn',ip_ebil_dyn)
387
388 !cc .... P. Le Van , ajout le 7/03/95 .pour le zoom ...
389 ! ......... ( modif le 17/04/96 ) .........
390
391
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 test_etatinit: IF (.not. etatinit) then
392 !Config Key = clon
393 !Config Desc = centre du zoom, longitude
394 !Config Def = 0
395 !Config Help = longitude en degres du centre
396 !Config du zoom
397 clonn = 0.
398 CALL getin('clon',clonn)
399
400 !Config Key = clat
401 !Config Desc = centre du zoom, latitude
402 !Config Def = 0
403 !Config Help = latitude en degres du centre du zoom
404 !Config
405 clatt = 0.
406 CALL getin('clat',clatt)
407
408 IF( ABS(clat - clatt).GE. 0.001 ) THEN
409 write(lunout,*)'conf_gcm: La valeur de clat passee par run.def', &
410 ' est differente de celle lue sur le fichier start '
411 STOP
412 ENDIF
413
414 !Config Key = grossismx
415 !Config Desc = zoom en longitude
416 !Config Def = 1.0
417 !Config Help = facteur de grossissement du zoom,
418 !Config selon la longitude
419 grossismxx = 1.0
420 CALL getin('grossismx',grossismxx)
421
422 IF( ABS(grossismx - grossismxx).GE. 0.001 ) THEN
423 write(lunout,*)'conf_gcm: La valeur de grossismx passee par ', &
424 'run.def est differente de celle lue sur le fichier start '
425 STOP
426 ENDIF
427
428 !Config Key = grossismy
429 !Config Desc = zoom en latitude
430 !Config Def = 1.0
431 !Config Help = facteur de grossissement du zoom,
432 !Config selon la latitude
433 grossismyy = 1.0
434 CALL getin('grossismy',grossismyy)
435
436 IF( ABS(grossismy - grossismyy).GE. 0.001 ) THEN
437 write(lunout,*)'conf_gcm: La valeur de grossismy passee par ', &
438 'run.def est differente de celle lue sur le fichier start '
439 STOP
440 ENDIF
441
442 IF( grossismx.LT.1. ) THEN
443 write(lunout,*) &
444 'conf_gcm: *** ATTENTION !! grossismx < 1 . *** '
445 STOP
446 ELSE
447 alphax = 1. - 1./ grossismx
448 ENDIF
449
450 IF( grossismy.LT.1. ) THEN
451 write(lunout,*) &
452 'conf_gcm: *** ATTENTION !! grossismy < 1 . *** '
453 STOP
454 ELSE
455 alphay = 1. - 1./ grossismy
456 ENDIF
457
458 write(lunout,*)'conf_gcm: alphax alphay',alphax,alphay
459
460 ! alphax et alphay sont les anciennes formulat. des grossissements
461
462 !Config Key = fxyhypb
463 !Config Desc = Fonction hyperbolique
464 !Config Def = y
465 !Config Help = Fonction f(y) hyperbolique si = .true.
466 !Config sinon sinusoidale
467 fxyhypbb = .TRUE.
468 CALL getin('fxyhypb',fxyhypbb)
469
470 IF( .NOT.fxyhypb ) THEN
471 IF( fxyhypbb ) THEN
472 write(lunout,*)' ******** PBS DANS CONF_GCM ******** '
473 write(lunout,*)' *** fxyhypb lu sur le fichier start est ', &
474 'F alors qu il est T sur run.def ***'
475 STOP
476 ENDIF
477 ELSE
478 IF( .NOT.fxyhypbb ) THEN
479 write(lunout,*)' ******** PBS DANS CONF_GCM ******** '
480 write(lunout,*)' *** fxyhypb lu sur le fichier start est ', &
481 'T alors qu il est F sur run.def **** '
482 STOP
483 ENDIF
484 ENDIF
485
486 !Config Key = dzoomx
487 !Config Desc = extension en longitude
488 !Config Def = 0
489 !Config Help = extension en longitude de la zone du zoom
490 !Config ( fraction de la zone totale)
491 dzoomxx = 0.0
492 CALL getin('dzoomx',dzoomxx)
493
494 IF( fxyhypb ) THEN
495 IF( ABS(dzoomx - dzoomxx).GE. 0.001 ) THEN
496 write(lunout,*)'conf_gcm: La valeur de dzoomx passee par ', &
497 'run.def est differente de celle lue sur le fichier start '
498 STOP
499 ENDIF
500 ENDIF
501
502 !Config Key = dzoomy
503 !Config Desc = extension en latitude
504 !Config Def = 0
505 !Config Help = extension en latitude de la zone du zoom
506 !Config ( fraction de la zone totale)
507 dzoomyy = 0.0
508 CALL getin('dzoomy',dzoomyy)
509
510 IF( fxyhypb ) THEN
511 IF( ABS(dzoomy - dzoomyy).GE. 0.001 ) THEN
512 write(lunout,*)'conf_gcm: La valeur de dzoomy passee par ', &
513 'run.def est differente de celle lue sur le fichier start '
514 STOP
515 ENDIF
516 ENDIF
517
518 !Config Key = taux
519 !Config Desc = raideur du zoom en X
520 !Config Def = 3
521 !Config Help = raideur du zoom en X
522 tauxx = 3.0
523 CALL getin('taux',tauxx)
524
525 IF( fxyhypb ) THEN
526 IF( ABS(taux - tauxx).GE. 0.001 ) THEN
527 write(lunout,*)'conf_gcm: La valeur de taux passee par ', &
528 'run.def est differente de celle lue sur le fichier start '
529 STOP
530 ENDIF
531 ENDIF
532
533 !Config Key = tauyy
534 !Config Desc = raideur du zoom en Y
535 !Config Def = 3
536 !Config Help = raideur du zoom en Y
537 tauyy = 3.0
538 CALL getin('tauy',tauyy)
539
540 IF( fxyhypb ) THEN
541 IF( ABS(tauy - tauyy).GE. 0.001 ) THEN
542 write(lunout,*)'conf_gcm: La valeur de tauy passee par ', &
543 'run.def est differente de celle lue sur le fichier start '
544 STOP
545 ENDIF
546 ENDIF
547
548 !c
549 IF( .NOT.fxyhypb ) THEN
550
551 !Config Key = ysinus
552 !Config IF = !fxyhypb
553 !Config Desc = Fonction en Sinus
554 !Config Def = y
555 !Config Help = Fonction f(y) avec y = Sin(latit.) si = .true.
556 !Config sinon y = latit.
557 ysinuss = .TRUE.
558 CALL getin('ysinus',ysinuss)
559
560 IF( .NOT.ysinus ) THEN
561 IF( ysinuss ) THEN
562 write(lunout,*)' ******** PBS DANS CONF_GCM ******** '
563 write(lunout,*)' *** ysinus lu sur le fichier start est F', &
564 ' alors qu il est T sur run.def ***'
565 STOP
566 ENDIF
567 ELSE
568 IF( .NOT.ysinuss ) THEN
569 write(lunout,*)' ******** PBS DANS CONF_GCM ******** '
570 write(lunout,*)' *** ysinus lu sur le fichier start est T', &
571 ' alors qu il est F sur run.def **** '
572 STOP
573 ENDIF
574 ENDIF
575 ENDIF ! of IF( .NOT.fxyhypb )
576
577 !Config Key = offline
578 !Config Desc = Nouvelle eau liquide
579 !Config Def = n
580 !Config Help = Permet de mettre en route la
581 !Config nouvelle parametrisation de l'eau liquide !
582 offline = .FALSE.
583 CALL getin('offline',offline)
584
585 !Config Key = type_trac
586 !Config Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
587 !Config Def = lmdz
588 !Config Help =
589 !Config 'lmdz' = pas de couplage, pur LMDZ
590 !Config 'inca' = model de chime INCA
591 !Config 'repr' = model de chime REPROBUS
592 !Config 'inco' = INCA + CO2i (temporaire)
593 type_trac = 'lmdz'
594 CALL getin('type_trac',type_trac)
595
596 !Config Key = config_inca
597 !Config Desc = Choix de configuration de INCA
598 !Config Def = none
599 !Config Help = Choix de configuration de INCA :
600 !Config 'none' = sans INCA
601 !Config 'chem' = INCA avec calcul de chemie
602 !Config 'aero' = INCA avec calcul des aerosols
603 config_inca = 'none'
604 CALL getin('config_inca',config_inca)
605
606 !Config Key = ok_dynzon
607 !Config Desc = calcul et sortie des transports
608 !Config Def = n
609 !Config Help = Permet de mettre en route le calcul des transports
610 !Config
611 ok_dynzon = .FALSE.
612 CALL getin('ok_dynzon',ok_dynzon)
613
614 !Config Key = ok_dyn_ins
615 !Config Desc = sorties instantanees dans la dynamique
616 !Config Def = n
617 !Config Help =
618 !Config
619 ok_dyn_ins = .FALSE.
620 CALL getin('ok_dyn_ins',ok_dyn_ins)
621
622 !Config Key = ok_dyn_ave
623 !Config Desc = sorties moyennes dans la dynamique
624 !Config Def = n
625 !Config Help =
626 !Config
627 ok_dyn_ave = .FALSE.
628 CALL getin('ok_dyn_ave',ok_dyn_ave)
629
630 write(lunout,*)' #########################################'
631 write(lunout,*)' Configuration des parametres du gcm: '
632 write(lunout,*)' planet_type = ', planet_type
633 write(lunout,*)' calend = ', calend
634 write(lunout,*)' dayref = ', dayref
635 write(lunout,*)' anneeref = ', anneeref
636 write(lunout,*)' nday = ', nday
637 write(lunout,*)' day_step = ', day_step
638 write(lunout,*)' iperiod = ', iperiod
639 write(lunout,*)' nsplit_phys = ', nsplit_phys
640 write(lunout,*)' iconser = ', iconser
641 write(lunout,*)' iecri = ', iecri
642 write(lunout,*)' periodav = ', periodav
643 write(lunout,*)' output_grads_dyn = ', output_grads_dyn
644 write(lunout,*)' dissip_period = ', dissip_period
645 write(lunout,*)' lstardis = ', lstardis
646 write(lunout,*)' nitergdiv = ', nitergdiv
647 write(lunout,*)' nitergrot = ', nitergrot
648 write(lunout,*)' niterh = ', niterh
649 write(lunout,*)' tetagdiv = ', tetagdiv
650 write(lunout,*)' tetagrot = ', tetagrot
651 write(lunout,*)' tetatemp = ', tetatemp
652 write(lunout,*)' coefdis = ', coefdis
653 write(lunout,*)' purmats = ', purmats
654 write(lunout,*)' read_start = ', read_start
655 write(lunout,*)' iflag_phys = ', iflag_phys
656 write(lunout,*)' iphysiq = ', iphysiq
657 write(lunout,*)' clonn = ', clonn
658 write(lunout,*)' clatt = ', clatt
659 write(lunout,*)' grossismx = ', grossismx
660 write(lunout,*)' grossismy = ', grossismy
661 write(lunout,*)' fxyhypbb = ', fxyhypbb
662 write(lunout,*)' dzoomxx = ', dzoomxx
663 write(lunout,*)' dzoomy = ', dzoomyy
664 write(lunout,*)' tauxx = ', tauxx
665 write(lunout,*)' tauyy = ', tauyy
666 write(lunout,*)' offline = ', offline
667 write(lunout,*)' type_trac = ', type_trac
668 write(lunout,*)' config_inca = ', config_inca
669 write(lunout,*)' ok_dynzon = ', ok_dynzon
670 write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
671 write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
672 else
673 !Config Key = clon
674 !Config Desc = centre du zoom, longitude
675 !Config Def = 0
676 !Config Help = longitude en degres du centre
677 !Config du zoom
678 1 clon = 0.
679 1 CALL getin('clon',clon)
680
681 !Config Key = clat
682 !Config Desc = centre du zoom, latitude
683 !Config Def = 0
684 !Config Help = latitude en degres du centre du zoom
685 !Config
686 1 clat = 0.
687 1 CALL getin('clat',clat)
688
689 !Config Key = grossismx
690 !Config Desc = zoom en longitude
691 !Config Def = 1.0
692 !Config Help = facteur de grossissement du zoom,
693 !Config selon la longitude
694 1 grossismx = 1.0
695 1 CALL getin('grossismx',grossismx)
696
697 !Config Key = grossismy
698 !Config Desc = zoom en latitude
699 !Config Def = 1.0
700 !Config Help = facteur de grossissement du zoom,
701 !Config selon la latitude
702 1 grossismy = 1.0
703 1 CALL getin('grossismy',grossismy)
704
705
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF( grossismx.LT.1. ) THEN
706 write(lunout,*) &
707 'conf_gcm: *** ATTENTION !! grossismx < 1 . *** '
708 STOP
709 ELSE
710 1 alphax = 1. - 1./ grossismx
711 ENDIF
712
713
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF( grossismy.LT.1. ) THEN
714 write(lunout,*) 'conf_gcm: ***ATTENTION !! grossismy < 1 . *** '
715 STOP
716 ELSE
717 1 alphay = 1. - 1./ grossismy
718 ENDIF
719
720 1 write(lunout,*)'conf_gcm: alphax alphay ',alphax,alphay
721
722 ! alphax et alphay sont les anciennes formulat. des grossissements
723
724 !Config Key = fxyhypb
725 !Config Desc = Fonction hyperbolique
726 !Config Def = y
727 !Config Help = Fonction f(y) hyperbolique si = .true.
728 !Config sinon sinusoidale
729 1 fxyhypb = .TRUE.
730 1 CALL getin('fxyhypb',fxyhypb)
731
732 !Config Key = dzoomx
733 !Config Desc = extension en longitude
734 !Config Def = 0
735 !Config Help = extension en longitude de la zone du zoom
736 !Config ( fraction de la zone totale)
737 1 dzoomx = 0.2
738 1 CALL getin('dzoomx',dzoomx)
739 1 call assert(dzoomx < 1, "conf_gcm: dzoomx must be < 1")
740
741 !Config Key = dzoomy
742 !Config Desc = extension en latitude
743 !Config Def = 0
744 !Config Help = extension en latitude de la zone du zoom
745 !Config ( fraction de la zone totale)
746 1 dzoomy = 0.2
747 1 CALL getin('dzoomy',dzoomy)
748 1 call assert(dzoomy < 1, "conf_gcm: dzoomy must be < 1")
749
750 !Config Key = taux
751 !Config Desc = raideur du zoom en X
752 !Config Def = 3
753 !Config Help = raideur du zoom en X
754 1 taux = 3.0
755 1 CALL getin('taux',taux)
756
757 !Config Key = tauy
758 !Config Desc = raideur du zoom en Y
759 !Config Def = 3
760 !Config Help = raideur du zoom en Y
761 1 tauy = 3.0
762 1 CALL getin('tauy',tauy)
763
764 !Config Key = ysinus
765 !Config IF = !fxyhypb
766 !Config Desc = Fonction en Sinus
767 !Config Def = y
768 !Config Help = Fonction f(y) avec y = Sin(latit.) si = .true.
769 !Config sinon y = latit.
770 1 ysinus = .TRUE.
771 1 CALL getin('ysinus',ysinus)
772
773 !Config Key = offline
774 !Config Desc = Nouvelle eau liquide
775 !Config Def = n
776 !Config Help = Permet de mettre en route la
777 !Config nouvelle parametrisation de l'eau liquide !
778 1 offline = .FALSE.
779 1 CALL getin('offline',offline)
780
781 !Config Key = type_trac
782 !Config Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
783 !Config Def = lmdz
784 !Config Help =
785 !Config 'lmdz' = pas de couplage, pur LMDZ
786 !Config 'inca' = model de chime INCA
787 !Config 'repr' = model de chime REPROBUS
788 !Config 'inco' = INCA + CO2i (temporaire)
789 1 type_trac = 'lmdz'
790 1 CALL getin('type_trac',type_trac)
791
792 !Config Key = config_inca
793 !Config Desc = Choix de configuration de INCA
794 !Config Def = none
795 !Config Help = Choix de configuration de INCA :
796 !Config 'none' = sans INCA
797 !Config 'chem' = INCA avec calcul de chemie
798 !Config 'aero' = INCA avec calcul des aerosols
799 1 config_inca = 'none'
800 1 CALL getin('config_inca',config_inca)
801
802 !Config Key = ok_dynzon
803 !Config Desc = sortie des transports zonaux dans la dynamique
804 !Config Def = n
805 !Config Help = Permet de mettre en route le calcul des transports
806 !Config
807 1 ok_dynzon = .FALSE.
808 1 CALL getin('ok_dynzon',ok_dynzon)
809
810 !Config Key = ok_dyn_ins
811 !Config Desc = sorties instantanees dans la dynamique
812 !Config Def = n
813 !Config Help =
814 !Config
815 1 ok_dyn_ins = .FALSE.
816 1 CALL getin('ok_dyn_ins',ok_dyn_ins)
817
818 !Config Key = ok_dyn_ave
819 !Config Desc = sorties moyennes dans la dynamique
820 !Config Def = n
821 !Config Help =
822 !Config
823 1 ok_dyn_ave = .FALSE.
824 1 CALL getin('ok_dyn_ave',ok_dyn_ave)
825
826 !Config key = ok_strato
827 !Config Desc = activation de la version strato
828 !Config Def = .FALSE.
829 !Config Help = active la version stratosph\'erique de LMDZ de F. Lott
830
831 1 ok_strato=.FALSE.
832 1 CALL getin('ok_strato',ok_strato)
833
834
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 vert_prof_dissip = merge(1, 0, ok_strato .and. llm==39)
835 1 CALL getin('vert_prof_dissip', vert_prof_dissip)
836 call assert(vert_prof_dissip == 0 .or. vert_prof_dissip == 1, &
837 1 "bad value for vert_prof_dissip")
838
839 !Config Key = ok_gradsfile
840 !Config Desc = activation des sorties grads du guidage
841 !Config Def = n
842 !Config Help = active les sorties grads du guidage
843
844 1 ok_gradsfile = .FALSE.
845 1 CALL getin('ok_gradsfile',ok_gradsfile)
846
847 !Config Key = ok_limit
848 !Config Desc = creation des fichiers limit dans create_etat0_limit
849 !Config Def = y
850 !Config Help = production du fichier limit.nc requise
851
852 1 ok_limit = .TRUE.
853 1 CALL getin('ok_limit',ok_limit)
854
855 !Config Key = ok_etat0
856 !Config Desc = creation des fichiers etat0 dans create_etat0_limit
857 !Config Def = y
858 !Config Help = production des fichiers start.nc, startphy.nc requise
859
860 1 ok_etat0 = .TRUE.
861 1 CALL getin('ok_etat0',ok_etat0)
862
863 !Config Key = read_orop
864 !Config Desc = lecture du fichier de params orographiques sous maille
865 !Config Def = f
866 !Config Help = lecture fichier plutot que grid_noro
867
868 1 read_orop = .FALSE.
869 1 CALL getin('read_orop',read_orop)
870
871 1 write(lunout,*)' #########################################'
872 write(lunout,*)' Configuration des parametres de cel0' &
873 1 //'_limit: '
874 1 write(lunout,*)' planet_type = ', planet_type
875 1 write(lunout,*)' calend = ', calend
876 1 write(lunout,*)' dayref = ', dayref
877 1 write(lunout,*)' anneeref = ', anneeref
878 1 write(lunout,*)' nday = ', nday
879 1 write(lunout,*)' day_step = ', day_step
880 1 write(lunout,*)' iperiod = ', iperiod
881 1 write(lunout,*)' iconser = ', iconser
882 1 write(lunout,*)' iecri = ', iecri
883 1 write(lunout,*)' periodav = ', periodav
884 1 write(lunout,*)' output_grads_dyn = ', output_grads_dyn
885 1 write(lunout,*)' dissip_period = ', dissip_period
886 1 write(lunout,*)' lstardis = ', lstardis
887 1 write(lunout,*)' nitergdiv = ', nitergdiv
888 1 write(lunout,*)' nitergrot = ', nitergrot
889 1 write(lunout,*)' niterh = ', niterh
890 1 write(lunout,*)' tetagdiv = ', tetagdiv
891 1 write(lunout,*)' tetagrot = ', tetagrot
892 1 write(lunout,*)' tetatemp = ', tetatemp
893 1 write(lunout,*)' coefdis = ', coefdis
894 1 write(lunout,*)' purmats = ', purmats
895 1 write(lunout,*)' read_start = ', read_start
896 1 write(lunout,*)' iflag_phys = ', iflag_phys
897 1 write(lunout,*)' iphysiq = ', iphysiq
898 1 write(lunout,*)' clon = ', clon
899 1 write(lunout,*)' clat = ', clat
900 1 write(lunout,*)' grossismx = ', grossismx
901 1 write(lunout,*)' grossismy = ', grossismy
902 1 write(lunout,*)' fxyhypb = ', fxyhypb
903 1 write(lunout,*)' dzoomx = ', dzoomx
904 1 write(lunout,*)' dzoomy = ', dzoomy
905 1 write(lunout,*)' taux = ', taux
906 1 write(lunout,*)' tauy = ', tauy
907 1 write(lunout,*)' offline = ', offline
908 1 write(lunout,*)' type_trac = ', type_trac
909 1 write(lunout,*)' config_inca = ', config_inca
910 1 write(lunout,*)' ok_dynzon = ', ok_dynzon
911 1 write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
912 1 write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
913 1 write(lunout,*)' ok_strato = ', ok_strato
914 1 write(lunout,*)' ok_gradsfile = ', ok_gradsfile
915 1 write(lunout,*)' ok_limit = ', ok_limit
916 1 write(lunout,*)' ok_etat0 = ', ok_etat0
917 1 write(lunout,*)' read_orop = ', read_orop
918 end IF test_etatinit
919
920 1 END SUBROUTINE conf_gcm
921