source: LMDZ6/trunk/libf/dyn3d/conf_gcm.f90 @ 5282

Last change on this file since 5282 was 5282, checked in by abarral, 6 hours ago

Turn iniprint.h clesphys.h into modules
Remove unused description.h

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