source: LMDZ6/branches/Amaury_dev/libf/dyn3d/lmdz_conf_gcm.f90 @ 5209

Last change on this file since 5209 was 5186, checked in by abarral, 9 days ago

Encapsulate files in modules

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