source: LMDZ5/branches/testing/libf/dyn3d/conf_gcm.F @ 2056

Last change on this file since 2056 was 2056, checked in by Laurent Fairhead, 10 years ago

Merged trunk changes r1997:2055 into testing branch

  • 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: 29.7 KB
Line 
1!
2! $Id: conf_gcm.F 2056 2014-06-11 13:46:46Z fairhead $
3!
4!
5!
6      SUBROUTINE conf_gcm( tapedef, etatinit, clesphy0 )
7!
8      USE control_mod
9#ifdef CPP_IOIPSL
10      use IOIPSL
11#else
12! if not using IOIPSL, we still need to use (a local version of) getin
13      use ioipsl_getincom
14#endif
15      USE infotrac, ONLY : type_trac
16      use assert_m, only: assert
17
18      IMPLICIT NONE
19!-----------------------------------------------------------------------
20!     Auteurs :   L. Fairhead , P. Le Van  .
21!
22!     Arguments :
23!
24!     tapedef   :
25!     etatinit  :     = TRUE   , on ne  compare pas les valeurs des para-
26!     -metres  du zoom  avec  celles lues sur le fichier start .
27!      clesphy0 :  sortie  .
28!
29       LOGICAL etatinit
30       INTEGER tapedef
31
32       INTEGER        longcles
33       PARAMETER(     longcles = 20 )
34       REAL clesphy0( longcles )
35!
36!   Declarations :
37!   --------------
38#include "dimensions.h"
39#include "paramet.h"
40#include "logic.h"
41#include "serre.h"
42#include "comdissnew.h"
43#include "temps.h"
44#include "comconst.h"
45
46! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
47! #include "clesphys.h"
48#include "iniprint.h"
49!
50!
51!   local:
52!   ------
53
54      CHARACTER ch1*72,ch2*72,ch3*72,ch4*12
55      REAL clonn,clatt,grossismxx,grossismyy
56      REAL dzoomxx,dzoomyy, tauxx,tauyy
57      LOGICAL  fxyhypbb, ysinuss
58      INTEGER i
59      LOGICAL use_filtre_fft
60!
61!  -------------------------------------------------------------------
62!
63!       .........     Version  du 29/04/97       ..........
64!
65!   Nouveaux parametres nitergdiv,nitergrot,niterh,tetagdiv,tetagrot,
66!      tetatemp   ajoutes  pour la dissipation   .
67!
68!   Autre parametre ajoute en fin de liste de tapedef : ** fxyhypb **
69!
70!  Si fxyhypb = .TRUE. , choix de la fonction a derivee tangente hyperb.
71!    Sinon , choix de fxynew  , a derivee sinusoidale  ..
72!
73!   ......  etatinit = . TRUE. si defrun  est appele dans ETAT0_LMD  ou
74!         LIMIT_LMD  pour l'initialisation de start.dat (dic) et
75!                de limit.dat ( dic)                        ...........
76!           Sinon  etatinit = . FALSE .
77!
78!   Donc etatinit = .F.  si on veut comparer les valeurs de  grossismx ,
79!    grossismy,clon,clat, fxyhypb  lues sur  le fichier  start  avec
80!   celles passees  par run.def ,  au debut du gcm, apres l'appel a
81!    lectba . 
82!   Ces parmetres definissant entre autres la grille et doivent etre
83!   pareils et coherents , sinon il y aura  divergence du gcm .
84!
85!-----------------------------------------------------------------------
86!   initialisations:
87!   ----------------
88
89!Config  Key  = lunout
90!Config  Desc = unite de fichier pour les impressions
91!Config  Def  = 6
92!Config  Help = unite de fichier pour les impressions
93!Config         (defaut sortie standard = 6)
94      lunout=6
95      CALL getin('lunout', lunout)
96      IF (lunout /= 5 .and. lunout /= 6) THEN
97        OPEN(UNIT=lunout,FILE='lmdz.out',ACTION='write',                     &
98     &          STATUS='unknown',FORM='formatted')
99      ENDIF
100
101!Config  Key  = prt_level
102!Config  Desc = niveau d'impressions de débogage
103!Config  Def  = 0
104!Config  Help = Niveau d'impression pour le débogage
105!Config         (0 = minimum d'impression)
106      prt_level = 0
107      CALL getin('prt_level',prt_level)
108
109!-----------------------------------------------------------------------
110!  Parametres de controle du run:
111!-----------------------------------------------------------------------
112!Config  Key  = planet_type
113!Config  Desc = planet type ("earth", "mars", "venus", ...)
114!Config  Def  = earth
115!Config  Help = this flag sets the type of atymosphere that is considered
116      planet_type="earth"
117      CALL getin('planet_type',planet_type)
118
119!Config  Key  = calend
120!Config  Desc = type de calendrier utilise
121!Config  Def  = earth_360d
122!Config  Help = valeur possible: earth_360d, earth_365d, earth_366d
123!Config         
124      calend = 'earth_360d'
125      CALL getin('calend', calend)
126
127!Config  Key  = dayref
128!Config  Desc = Jour de l'etat initial
129!Config  Def  = 1
130!Config  Help = Jour de l'etat initial ( = 350  si 20 Decembre ,
131!Config         par expl. ,comme ici ) ... A completer
132      dayref=1
133      CALL getin('dayref', dayref)
134
135!Config  Key  = anneeref
136!Config  Desc = Annee de l'etat initial
137!Config  Def  = 1998
138!Config  Help = Annee de l'etat  initial
139!Config         (   avec  4  chiffres   ) ... A completer
140      anneeref = 1998
141      CALL getin('anneeref',anneeref)
142
143!Config  Key  = raz_date
144!Config  Desc = Remise a zero de la date initiale
145!Config  Def  = 0 (pas de remise a zero)
146!Config  Help = Remise a zero de la date initiale
147!Config         0 pas de remise a zero, on garde la date du fichier restart
148!Config         1 prise en compte de la date de gcm.def avec remise a zero
149!Config         des compteurs de pas de temps
150      raz_date = 0
151      CALL getin('raz_date', raz_date)
152
153!Config  Key  = nday
154!Config  Desc = Nombre de jours d'integration
155!Config  Def  = 10
156!Config  Help = Nombre de jours d'integration
157!Config         ... On pourait aussi permettre des mois ou des annees !
158      nday = 10
159      CALL getin('nday',nday)
160
161!Config  Key  = starttime
162!Config  Desc = Heure de depart de la simulation
163!Config  Def  = 0
164!Config  Help = Heure de depart de la simulation
165!Config         en jour
166      starttime = 0
167      CALL getin('starttime',starttime)
168
169!Config  Key  = day_step
170!Config  Desc = nombre de pas par jour
171!Config  Def  = 240
172!Config  Help = nombre de pas par jour (multiple de iperiod) (
173!Config          ici pour  dt = 1 min )
174       day_step = 240
175       CALL getin('day_step',day_step)
176
177!Config  Key  = nsplit_phys
178       nsplit_phys = 1
179       CALL getin('nsplit_phys',nsplit_phys)
180
181!Config  Key  = iperiod
182!Config  Desc = periode pour le pas Matsuno
183!Config  Def  = 5
184!Config  Help = periode pour le pas Matsuno (en pas de temps)
185       iperiod = 5
186       CALL getin('iperiod',iperiod)
187
188!Config  Key  = iapp_tracvl
189!Config  Desc = frequence du groupement des flux
190!Config  Def  = iperiod
191!Config  Help = frequence du groupement des flux (en pas de temps)
192       iapp_tracvl = iperiod
193       CALL getin('iapp_tracvl',iapp_tracvl)
194
195!Config  Key  = iconser
196!Config  Desc = periode de sortie des variables de controle
197!Config  Def  = 240 
198!Config  Help = periode de sortie des variables de controle
199!Config         (En pas de temps)
200       iconser = 240 
201       CALL getin('iconser', iconser)
202
203!Config  Key  = iecri
204!Config  Desc = periode d'ecriture du fichier histoire
205!Config  Def  = 1
206!Config  Help = periode d'ecriture du fichier histoire (en jour)
207       iecri = 1
208       CALL getin('iecri',iecri)
209
210
211!Config  Key  = periodav
212!Config  Desc = periode de stockage fichier histmoy
213!Config  Def  = 1
214!Config  Help = periode de stockage fichier histmoy (en jour)
215       periodav = 1.
216       CALL getin('periodav',periodav)
217
218!Config  Key  = output_grads_dyn
219!Config  Desc = output dynamics diagnostics in 'dyn.dat' file
220!Config  Def  = n
221!Config  Help = output dynamics diagnostics in Grads-readable 'dyn.dat' file
222       output_grads_dyn=.false.
223       CALL getin('output_grads_dyn',output_grads_dyn)
224
225!Config  Key  = dissip_period
226!Config  Desc = periode de la dissipation
227!Config  Def  = 0
228!Config  Help = periode de la dissipation
229!Config  dissip_period=0 => la valeur sera calcule dans inidissip       
230!Config  dissip_period>0 => on prend cette valeur
231       dissip_period = 0
232       CALL getin('dissip_period',dissip_period)
233
234!cc  ....   P. Le Van , modif le 29/04/97 .pour la dissipation  ...
235!cc
236
237!Config  Key  = lstardis
238!Config  Desc = choix de l'operateur de dissipation
239!Config  Def  = y
240!Config  Help = choix de l'operateur de dissipation
241!Config         'y' si on veut star et 'n' si on veut non-start !
242!Config         Moi y en a pas comprendre !
243       lstardis = .TRUE.
244       CALL getin('lstardis',lstardis)
245
246
247!Config  Key  = nitergdiv
248!Config  Desc = Nombre d'iteration de gradiv
249!Config  Def  = 1
250!Config  Help = nombre d'iterations de l'operateur de dissipation
251!Config         gradiv
252       nitergdiv = 1
253       CALL getin('nitergdiv',nitergdiv)
254
255!Config  Key  = nitergrot
256!Config  Desc = nombre d'iterations de nxgradrot
257!Config  Def  = 2
258!Config  Help = nombre d'iterations de l'operateur de dissipation 
259!Config         nxgradrot
260       nitergrot = 2
261       CALL getin('nitergrot',nitergrot)
262
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       niterh = 2
270       CALL getin('niterh',niterh)
271
272
273!Config  Key  = tetagdiv
274!Config  Desc = temps de dissipation pour div
275!Config  Def  = 7200
276!Config  Help = temps de dissipation des plus petites longeur
277!Config         d'ondes pour u,v (gradiv)
278       tetagdiv = 7200.
279       CALL getin('tetagdiv',tetagdiv)
280
281!Config  Key  = tetagrot
282!Config  Desc = temps de dissipation pour grad
283!Config  Def  = 7200
284!Config  Help = temps de dissipation des plus petites longeur
285!Config         d'ondes pour u,v (nxgradrot)
286       tetagrot = 7200.
287       CALL getin('tetagrot',tetagrot)
288
289!Config  Key  = tetatemp
290!Config  Desc = temps de dissipation pour h
291!Config  Def  = 7200
292!Config  Help =  temps de dissipation des plus petites longeur
293!Config         d'ondes pour h (divgrad)   
294       tetatemp  = 7200.
295       CALL getin('tetatemp',tetatemp )
296
297! Parametres controlant la variation sur la verticale des constantes de
298! dissipation.
299! Pour le moment actifs uniquement dans la version a 39 niveaux
300! avec ok_strato=y
301
302       dissip_factz=4.
303       dissip_deltaz=10.
304       dissip_zref=30.
305       CALL getin('dissip_factz',dissip_factz )
306       CALL getin('dissip_deltaz',dissip_deltaz )
307       CALL getin('dissip_zref',dissip_zref )
308
309! top_bound sponge: only active if ok_strato=.true. and iflag_top_bound!=0
310!                   iflag_top_bound=0 for no sponge
311!                   iflag_top_bound=1 for sponge over 4 topmost layers
312!                   iflag_top_bound=2 for sponge from top to ~1% of top layer pressure
313       iflag_top_bound=1
314       CALL getin('iflag_top_bound',iflag_top_bound)
315
316! mode_top_bound : fields towards which sponge relaxation will be done:
317!                  mode_top_bound=0: no relaxation
318!                  mode_top_bound=1: u and v relax towards 0
319!                  mode_top_bound=2: u and v relax towards their zonal mean
320!                  mode_top_bound=3: u,v and pot. temp. relax towards their zonal mean
321       mode_top_bound=3
322       CALL getin('mode_top_bound',mode_top_bound)
323
324! top_bound sponge : inverse of charactericstic relaxation time scale for sponge
325       tau_top_bound=1.e-5
326       CALL getin('tau_top_bound',tau_top_bound)
327
328!Config  Key  = coefdis
329!Config  Desc = coefficient pour gamdissip
330!Config  Def  = 0
331!Config  Help = coefficient pour gamdissip 
332       coefdis = 0.
333       CALL getin('coefdis',coefdis)
334
335!Config  Key  = purmats
336!Config  Desc = Schema d'integration
337!Config  Def  = n
338!Config  Help = Choix du schema d'integration temporel.
339!Config         y = pure Matsuno sinon c'est du Matsuno-leapfrog
340       purmats = .FALSE.
341       CALL getin('purmats',purmats)
342
343!Config  Key  = ok_guide
344!Config  Desc = Guidage
345!Config  Def  = n
346!Config  Help = Guidage
347       ok_guide = .FALSE.
348       CALL getin('ok_guide',ok_guide)
349
350!    ...............................................................
351
352!Config  Key  =  read_start
353!Config  Desc = Initialize model using a 'start.nc' file
354!Config  Def  = y
355!Config  Help = y: intialize dynamical fields using a 'start.nc' file
356!               n: fields are initialized by 'iniacademic' routine
357       read_start= .true.
358       CALL getin('read_start',read_start)
359
360!Config  Key  = iflag_phys
361!Config  Desc = Avec ls physique
362!Config  Def  = 1
363!Config  Help = Permet de faire tourner le modele sans
364!Config         physique.
365       iflag_phys = 1
366       CALL getin('iflag_phys',iflag_phys)
367
368
369!Config  Key  =  iphysiq
370!Config  Desc = Periode de la physique
371!Config  Def  = 5
372!Config  Help = Periode de la physique en pas de temps de la dynamique.
373       iphysiq = 5
374       CALL getin('iphysiq', iphysiq)
375
376!Config  Key  = ip_ebil_dyn
377!Config  Desc = PRINT level for energy conserv. diag.
378!Config  Def  = 0
379!Config  Help = PRINT level for energy conservation diag. ;
380!               les options suivantes existent :
381!Config         0 pas de print
382!Config         1 pas de print
383!Config         2 print,
384       ip_ebil_dyn = 0
385       CALL getin('ip_ebil_dyn',ip_ebil_dyn)
386!
387
388      DO i = 1, longcles
389       clesphy0(i) = 0.
390      ENDDO
391
392!cc  ....   P. Le Van , ajout  le 7/03/95 .pour le zoom ...
393!     .........   (  modif  le 17/04/96 )   .........
394!
395      IF( etatinit ) GO TO 100
396
397!Config  Key  = clon
398!Config  Desc = centre du zoom, longitude
399!Config  Def  = 0
400!Config  Help = longitude en degres du centre
401!Config         du zoom
402       clonn = 0.
403       CALL getin('clon',clonn)
404
405!Config  Key  = clat
406!Config  Desc = centre du zoom, latitude
407!Config  Def  = 0
408!Config  Help = latitude en degres du centre du zoom
409!Config         
410       clatt = 0.
411       CALL getin('clat',clatt)
412
413!
414!
415      IF( ABS(clat - clatt).GE. 0.001 )  THEN
416        write(lunout,*)'conf_gcm: La valeur de clat passee par run.def',     &
417     &    ' est differente de celle lue sur le fichier  start '
418        STOP
419      ENDIF
420
421!Config  Key  = grossismx
422!Config  Desc = zoom en longitude
423!Config  Def  = 1.0
424!Config  Help = facteur de grossissement du zoom,
425!Config         selon la longitude
426       grossismxx = 1.0
427       CALL getin('grossismx',grossismxx)
428
429
430      IF( ABS(grossismx - grossismxx).GE. 0.001 )  THEN
431        write(lunout,*)'conf_gcm: La valeur de grossismx passee par ',       &
432     &  'run.def est differente de celle lue sur le fichier  start '
433        STOP
434      ENDIF
435
436!Config  Key  = grossismy
437!Config  Desc = zoom en latitude
438!Config  Def  = 1.0
439!Config  Help = facteur de grossissement du zoom,
440!Config         selon la latitude
441       grossismyy = 1.0
442       CALL getin('grossismy',grossismyy)
443
444      IF( ABS(grossismy - grossismyy).GE. 0.001 )  THEN
445        write(lunout,*)'conf_gcm: La valeur de grossismy passee par ',        &
446     & 'run.def est differente de celle lue sur le fichier  start '
447        STOP
448      ENDIF
449     
450      IF( grossismx.LT.1. )  THEN
451        write(lunout,*)                                                        &
452     &       'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
453         STOP
454      ELSE
455         alphax = 1. - 1./ grossismx
456      ENDIF
457
458
459      IF( grossismy.LT.1. )  THEN
460        write(lunout,*)                                                        &
461     &       'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
462         STOP
463      ELSE
464         alphay = 1. - 1./ grossismy
465      ENDIF
466
467      write(lunout,*)'conf_gcm: alphax alphay',alphax,alphay
468!
469!    alphax et alphay sont les anciennes formulat. des grossissements
470!
471!
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              STOP
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              STOP
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        STOP
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        STOP
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        STOP
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        STOP
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            STOP
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              STOP
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      type_trac = 'lmdz'
604      CALL getin('type_trac',type_trac)
605
606!Config  Key  = config_inca
607!Config  Desc = Choix de configuration de INCA
608!Config  Def  = none
609!Config  Help = Choix de configuration de INCA :
610!Config         'none' = sans INCA
611!Config         'chem' = INCA avec calcul de chemie
612!Config         'aero' = INCA avec calcul des aerosols
613      config_inca = 'none'
614      CALL getin('config_inca',config_inca)
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,*)' config_inca = ', config_inca
679      write(lunout,*)' ok_dynzon = ', ok_dynzon
680      write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
681      write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
682
683      RETURN
684!   ...............................................
685!
686100   CONTINUE
687!Config  Key  = clon
688!Config  Desc = centre du zoom, longitude
689!Config  Def  = 0
690!Config  Help = longitude en degres du centre
691!Config         du zoom
692       clon = 0.
693       CALL getin('clon',clon)
694
695!Config  Key  = clat
696!Config  Desc = centre du zoom, latitude
697!Config  Def  = 0
698!Config  Help = latitude en degres du centre du zoom
699!Config         
700       clat = 0.
701       CALL getin('clat',clat)
702
703!Config  Key  = grossismx
704!Config  Desc = zoom en longitude
705!Config  Def  = 1.0
706!Config  Help = facteur de grossissement du zoom,
707!Config         selon la longitude
708       grossismx = 1.0
709       CALL getin('grossismx',grossismx)
710
711!Config  Key  = grossismy
712!Config  Desc = zoom en latitude
713!Config  Def  = 1.0
714!Config  Help = facteur de grossissement du zoom,
715!Config         selon la latitude
716       grossismy = 1.0
717       CALL getin('grossismy',grossismy)
718
719      IF( grossismx.LT.1. )  THEN
720        write(lunout,*)'conf_gcm: ***ATTENTION !! grossismx < 1 . *** '
721         STOP
722      ELSE
723         alphax = 1. - 1./ grossismx
724      ENDIF
725
726
727      IF( grossismy.LT.1. )  THEN
728        write(lunout,*) 'conf_gcm: ***ATTENTION !! grossismy < 1 . *** '
729         STOP
730      ELSE
731         alphay = 1. - 1./ grossismy
732      ENDIF
733
734      write(lunout,*)'conf_gcm: alphax alphay ',alphax,alphay
735!
736!    alphax et alphay sont les anciennes formulat. des grossissements
737!
738!
739
740!Config  Key  = fxyhypb
741!Config  Desc = Fonction  hyperbolique
742!Config  Def  = y
743!Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
744!Config         sinon  sinusoidale
745       fxyhypb = .TRUE.
746       CALL getin('fxyhypb',fxyhypb)
747
748!Config  Key  = dzoomx
749!Config  Desc = extension en longitude
750!Config  Def  = 0
751!Config  Help = extension en longitude  de la zone du zoom 
752!Config         ( fraction de la zone totale)
753       dzoomx = 0.0
754       CALL getin('dzoomx',dzoomx)
755
756!Config  Key  = dzoomy
757!Config  Desc = extension en latitude
758!Config  Def  = 0
759!Config  Help = extension en latitude de la zone  du zoom 
760!Config         ( fraction de la zone totale)
761       dzoomy = 0.0
762       CALL getin('dzoomy',dzoomy)
763
764!Config  Key  = taux
765!Config  Desc = raideur du zoom en  X
766!Config  Def  = 3
767!Config  Help = raideur du zoom en  X
768       taux = 3.0
769       CALL getin('taux',taux)
770
771!Config  Key  = tauy
772!Config  Desc = raideur du zoom en  Y
773!Config  Def  = 3
774!Config  Help = raideur du zoom en  Y
775       tauy = 3.0
776       CALL getin('tauy',tauy)
777
778!Config  Key  = ysinus
779!Config  IF   = !fxyhypb
780!Config  Desc = Fonction en Sinus
781!Config  Def  = y
782!Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
783!Config         sinon y = latit.
784       ysinus = .TRUE.
785       CALL getin('ysinus',ysinus)
786!
787!Config  Key  = offline
788!Config  Desc = Nouvelle eau liquide
789!Config  Def  = n
790!Config  Help = Permet de mettre en route la
791!Config         nouvelle parametrisation de l'eau liquide !
792       offline = .FALSE.
793       CALL getin('offline',offline)
794
795!Config  Key  = type_trac
796!Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
797!Config  Def  = lmdz
798!Config  Help =
799!Config         'lmdz' = pas de couplage, pur LMDZ
800!Config         'inca' = model de chime INCA
801!Config         'repr' = model de chime REPROBUS
802      type_trac = 'lmdz'
803      CALL getin('type_trac',type_trac)
804
805!Config  Key  = config_inca
806!Config  Desc = Choix de configuration de INCA
807!Config  Def  = none
808!Config  Help = Choix de configuration de INCA :
809!Config         'none' = sans INCA
810!Config         'chem' = INCA avec calcul de chemie
811!Config         'aero' = INCA avec calcul des aerosols
812      config_inca = 'none'
813      CALL getin('config_inca',config_inca)
814
815!Config  Key  = ok_dynzon
816!Config  Desc = sortie des transports zonaux dans la dynamique
817!Config  Def  = n
818!Config  Help = Permet de mettre en route le calcul des transports
819!Config         
820      ok_dynzon = .FALSE.
821      CALL getin('ok_dynzon',ok_dynzon)
822
823!Config  Key  = ok_dyn_ins
824!Config  Desc = sorties instantanees dans la dynamique
825!Config  Def  = n
826!Config  Help =
827!Config         
828      ok_dyn_ins = .FALSE.
829      CALL getin('ok_dyn_ins',ok_dyn_ins)
830
831!Config  Key  = ok_dyn_ave
832!Config  Desc = sorties moyennes dans la dynamique
833!Config  Def  = n
834!Config  Help =
835!Config         
836      ok_dyn_ave = .FALSE.
837      CALL getin('ok_dyn_ave',ok_dyn_ave)
838
839!Config  Key  = use_filtre_fft
840!Config  Desc = flag d'activation des FFT pour le filtre
841!Config  Def  = false
842!Config  Help = permet d'activer l'utilisation des FFT pour effectuer
843!Config         le filtrage aux poles.
844! Le filtre fft n'est pas implemente dans dyn3d
845      use_filtre_fft=.FALSE.
846      CALL getin('use_filtre_fft',use_filtre_fft)
847
848      IF (use_filtre_fft) THEN
849        write(lunout,*)'STOP !!!'
850        write(lunout,*)'use_filtre_fft n est pas implemente dans dyn3d'
851        STOP 1
852      ENDIF
853     
854!Config key = ok_strato
855!Config  Desc = activation de la version strato
856!Config  Def  = .FALSE.
857!Config  Help = active la version stratosphérique de LMDZ de F. Lott
858
859      ok_strato=.FALSE.
860      CALL getin('ok_strato',ok_strato)
861
862      vert_prof_dissip = merge(1, 0, ok_strato .and. llm==39)
863      CALL getin('vert_prof_dissip', vert_prof_dissip)
864      call assert(vert_prof_dissip == 0 .or. vert_prof_dissip ==  1,        &
865     &     "bad value for vert_prof_dissip")
866
867!Config  Key  = ok_gradsfile
868!Config  Desc = activation des sorties grads du guidage
869!Config  Def  = n
870!Config  Help = active les sorties grads du guidage
871
872       ok_gradsfile = .FALSE.
873       CALL getin('ok_gradsfile',ok_gradsfile)
874
875!Config  Key  = ok_limit
876!Config  Desc = creation des fichiers limit dans create_etat0_limit
877!Config  Def  = y
878!Config  Help = production du fichier limit.nc requise
879
880       ok_limit = .TRUE.
881       CALL getin('ok_limit',ok_limit)
882
883!Config  Key  = ok_etat0
884!Config  Desc = creation des fichiers etat0 dans create_etat0_limit
885!Config  Def  = y
886!Config  Help = production des fichiers start.nc, startphy.nc requise
887
888      ok_etat0 = .TRUE.
889      CALL getin('ok_etat0',ok_etat0)
890
891      write(lunout,*)' #########################################'
892      write(lunout,*)' Configuration des parametres de cel0'                &
893     &             //'_limit: '
894      write(lunout,*)' planet_type = ', planet_type
895      write(lunout,*)' calend = ', calend
896      write(lunout,*)' dayref = ', dayref
897      write(lunout,*)' anneeref = ', anneeref
898      write(lunout,*)' nday = ', nday
899      write(lunout,*)' day_step = ', day_step
900      write(lunout,*)' iperiod = ', iperiod
901      write(lunout,*)' iconser = ', iconser
902      write(lunout,*)' iecri = ', iecri
903      write(lunout,*)' periodav = ', periodav
904      write(lunout,*)' output_grads_dyn = ', output_grads_dyn
905      write(lunout,*)' dissip_period = ', dissip_period
906      write(lunout,*)' lstardis = ', lstardis
907      write(lunout,*)' nitergdiv = ', nitergdiv
908      write(lunout,*)' nitergrot = ', nitergrot
909      write(lunout,*)' niterh = ', niterh
910      write(lunout,*)' tetagdiv = ', tetagdiv
911      write(lunout,*)' tetagrot = ', tetagrot
912      write(lunout,*)' tetatemp = ', tetatemp
913      write(lunout,*)' coefdis = ', coefdis
914      write(lunout,*)' purmats = ', purmats
915      write(lunout,*)' read_start = ', read_start
916      write(lunout,*)' iflag_phys = ', iflag_phys
917      write(lunout,*)' iphysiq = ', iphysiq
918      write(lunout,*)' clon = ', clon
919      write(lunout,*)' clat = ', clat
920      write(lunout,*)' grossismx = ', grossismx
921      write(lunout,*)' grossismy = ', grossismy
922      write(lunout,*)' fxyhypb = ', fxyhypb
923      write(lunout,*)' dzoomx = ', dzoomx
924      write(lunout,*)' dzoomy = ', dzoomy
925      write(lunout,*)' taux = ', taux
926      write(lunout,*)' tauy = ', tauy
927      write(lunout,*)' offline = ', offline
928      write(lunout,*)' type_trac = ', type_trac
929      write(lunout,*)' config_inca = ', config_inca
930      write(lunout,*)' ok_dynzon = ', ok_dynzon
931      write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
932      write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
933      write(lunout,*)' ok_strato = ', ok_strato
934      write(lunout,*)' ok_gradsfile = ', ok_gradsfile
935      write(lunout,*)' ok_limit = ', ok_limit
936      write(lunout,*)' ok_etat0 = ', ok_etat0
937!
938      RETURN
939      END
Note: See TracBrowser for help on using the repository browser.