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

Last change on this file since 1707 was 1707, checked in by Laurent Fairhead, 11 years ago

Version testing basée sur la r1706


Testing release based on r1706

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 29.0 KB
Line 
1!
2! $Id: conf_gcm.F 1707 2013-01-11 09:19:19Z fairhead $
3!
4c
5c
6      SUBROUTINE conf_gcm( tapedef, etatinit, clesphy0 )
7c
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
19c-----------------------------------------------------------------------
20c     Auteurs :   L. Fairhead , P. Le Van  .
21c
22c     Arguments :
23c
24c     tapedef   :
25c     etatinit  :     = TRUE   , on ne  compare pas les valeurs des para-
26c     -metres  du zoom  avec  celles lues sur le fichier start .
27c      clesphy0 :  sortie  .
28c
29       LOGICAL etatinit
30       INTEGER tapedef
31
32       INTEGER        longcles
33       PARAMETER(     longcles = 20 )
34       REAL clesphy0( longcles )
35c
36c   Declarations :
37c   --------------
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"
49c
50c
51c   local:
52c   ------
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
60c
61c  -------------------------------------------------------------------
62c
63c       .........     Version  du 29/04/97       ..........
64c
65c   Nouveaux parametres nitergdiv,nitergrot,niterh,tetagdiv,tetagrot,
66c      tetatemp   ajoutes  pour la dissipation   .
67c
68c   Autre parametre ajoute en fin de liste de tapedef : ** fxyhypb **
69c
70c  Si fxyhypb = .TRUE. , choix de la fonction a derivee tangente hyperb.
71c    Sinon , choix de fxynew  , a derivee sinusoidale  ..
72c
73c   ......  etatinit = . TRUE. si defrun  est appele dans ETAT0_LMD  ou
74c         LIMIT_LMD  pour l'initialisation de start.dat (dic) et
75c                de limit.dat ( dic)                        ...........
76c           Sinon  etatinit = . FALSE .
77c
78c   Donc etatinit = .F.  si on veut comparer les valeurs de  grossismx ,
79c    grossismy,clon,clat, fxyhypb  lues sur  le fichier  start  avec
80c   celles passees  par run.def ,  au debut du gcm, apres l'appel a
81c    lectba . 
82c   Ces parmetres definissant entre autres la grille et doivent etre
83c   pareils et coherents , sinon il y aura  divergence du gcm .
84c
85c-----------------------------------------------------------------------
86c   initialisations:
87c   ----------------
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
109c-----------------------------------------------------------------------
110c  Parametres de controle du run:
111c-----------------------------------------------------------------------
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
234ccc  ....   P. Le Van , modif le 29/04/97 .pour la dissipation  ...
235ccc
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       iflag_top_bound=1
310       tau_top_bound=1.e-5
311       CALL getin('iflag_top_bound',iflag_top_bound)
312       CALL getin('tau_top_bound',tau_top_bound)
313
314!Config  Key  = coefdis
315!Config  Desc = coefficient pour gamdissip
316!Config  Def  = 0
317!Config  Help = coefficient pour gamdissip 
318       coefdis = 0.
319       CALL getin('coefdis',coefdis)
320
321!Config  Key  = purmats
322!Config  Desc = Schema d'integration
323!Config  Def  = n
324!Config  Help = Choix du schema d'integration temporel.
325!Config         y = pure Matsuno sinon c'est du Matsuno-leapfrog
326       purmats = .FALSE.
327       CALL getin('purmats',purmats)
328
329!Config  Key  = ok_guide
330!Config  Desc = Guidage
331!Config  Def  = n
332!Config  Help = Guidage
333       ok_guide = .FALSE.
334       CALL getin('ok_guide',ok_guide)
335
336c    ...............................................................
337
338!Config  Key  =  read_start
339!Config  Desc = Initialize model using a 'start.nc' file
340!Config  Def  = y
341!Config  Help = y: intialize dynamical fields using a 'start.nc' file
342!               n: fields are initialized by 'iniacademic' routine
343       read_start= .true.
344       CALL getin('read_start',read_start)
345
346!Config  Key  = iflag_phys
347!Config  Desc = Avec ls physique
348!Config  Def  = 1
349!Config  Help = Permet de faire tourner le modele sans
350!Config         physique.
351       iflag_phys = 1
352       CALL getin('iflag_phys',iflag_phys)
353
354
355!Config  Key  =  iphysiq
356!Config  Desc = Periode de la physique
357!Config  Def  = 5
358!Config  Help = Periode de la physique en pas de temps de la dynamique.
359       iphysiq = 5
360       CALL getin('iphysiq', iphysiq)
361
362!Config  Key  = ip_ebil_dyn
363!Config  Desc = PRINT level for energy conserv. diag.
364!Config  Def  = 0
365!Config  Help = PRINT level for energy conservation diag. ;
366!               les options suivantes existent :
367!Config         0 pas de print
368!Config         1 pas de print
369!Config         2 print,
370       ip_ebil_dyn = 0
371       CALL getin('ip_ebil_dyn',ip_ebil_dyn)
372!
373
374      DO i = 1, longcles
375       clesphy0(i) = 0.
376      ENDDO
377
378ccc  ....   P. Le Van , ajout  le 7/03/95 .pour le zoom ...
379c     .........   (  modif  le 17/04/96 )   .........
380c
381      IF( etatinit ) GO TO 100
382
383!Config  Key  = clon
384!Config  Desc = centre du zoom, longitude
385!Config  Def  = 0
386!Config  Help = longitude en degres du centre
387!Config         du zoom
388       clonn = 0.
389       CALL getin('clon',clonn)
390
391!Config  Key  = clat
392!Config  Desc = centre du zoom, latitude
393!Config  Def  = 0
394!Config  Help = latitude en degres du centre du zoom
395!Config         
396       clatt = 0.
397       CALL getin('clat',clatt)
398
399c
400c
401      IF( ABS(clat - clatt).GE. 0.001 )  THEN
402        write(lunout,*)'conf_gcm: La valeur de clat passee par run.def',
403     &    ' est differente de celle lue sur le fichier  start '
404        STOP
405      ENDIF
406
407!Config  Key  = grossismx
408!Config  Desc = zoom en longitude
409!Config  Def  = 1.0
410!Config  Help = facteur de grossissement du zoom,
411!Config         selon la longitude
412       grossismxx = 1.0
413       CALL getin('grossismx',grossismxx)
414
415
416      IF( ABS(grossismx - grossismxx).GE. 0.001 )  THEN
417        write(lunout,*)'conf_gcm: La valeur de grossismx passee par ',
418     &  'run.def est differente de celle lue sur le fichier  start '
419        STOP
420      ENDIF
421
422!Config  Key  = grossismy
423!Config  Desc = zoom en latitude
424!Config  Def  = 1.0
425!Config  Help = facteur de grossissement du zoom,
426!Config         selon la latitude
427       grossismyy = 1.0
428       CALL getin('grossismy',grossismyy)
429
430      IF( ABS(grossismy - grossismyy).GE. 0.001 )  THEN
431        write(lunout,*)'conf_gcm: La valeur de grossismy passee par ',
432     & 'run.def est differente de celle lue sur le fichier  start '
433        STOP
434      ENDIF
435     
436      IF( grossismx.LT.1. )  THEN
437        write(lunout,*)
438     &       'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
439         STOP
440      ELSE
441         alphax = 1. - 1./ grossismx
442      ENDIF
443
444
445      IF( grossismy.LT.1. )  THEN
446        write(lunout,*)
447     &       'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
448         STOP
449      ELSE
450         alphay = 1. - 1./ grossismy
451      ENDIF
452
453      write(lunout,*)'conf_gcm: alphax alphay',alphax,alphay
454c
455c    alphax et alphay sont les anciennes formulat. des grossissements
456c
457c
458
459!Config  Key  = fxyhypb
460!Config  Desc = Fonction  hyperbolique
461!Config  Def  = y
462!Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
463!Config         sinon  sinusoidale
464       fxyhypbb = .TRUE.
465       CALL getin('fxyhypb',fxyhypbb)
466
467      IF( .NOT.fxyhypb )  THEN
468         IF( fxyhypbb )     THEN
469            write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
470            write(lunout,*)' *** fxyhypb lu sur le fichier start est ',
471     *       'F alors  qu il est  T  sur  run.def  ***'
472              STOP
473         ENDIF
474      ELSE
475         IF( .NOT.fxyhypbb )   THEN
476            write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
477            write(lunout,*)' ***  fxyhypb lu sur le fichier start est ',
478     *        'T alors  qu il est  F  sur  run.def  ****  '
479              STOP
480         ENDIF
481      ENDIF
482c
483!Config  Key  = dzoomx
484!Config  Desc = extension en longitude
485!Config  Def  = 0
486!Config  Help = extension en longitude  de la zone du zoom 
487!Config         ( fraction de la zone totale)
488       dzoomxx = 0.0
489       CALL getin('dzoomx',dzoomxx)
490
491      IF( fxyhypb )  THEN
492       IF( ABS(dzoomx - dzoomxx).GE. 0.001 )  THEN
493        write(lunout,*)'conf_gcm: La valeur de dzoomx passee par ',
494     *  'run.def est differente de celle lue sur le fichier  start '
495        STOP
496       ENDIF
497      ENDIF
498
499!Config  Key  = dzoomy
500!Config  Desc = extension en latitude
501!Config  Def  = 0
502!Config  Help = extension en latitude de la zone  du zoom 
503!Config         ( fraction de la zone totale)
504       dzoomyy = 0.0
505       CALL getin('dzoomy',dzoomyy)
506
507      IF( fxyhypb )  THEN
508       IF( ABS(dzoomy - dzoomyy).GE. 0.001 )  THEN
509        write(lunout,*)'conf_gcm: La valeur de dzoomy passee par ',
510     * 'run.def est differente de celle lue sur le fichier  start '
511        STOP
512       ENDIF
513      ENDIF
514     
515!Config  Key  = taux
516!Config  Desc = raideur du zoom en  X
517!Config  Def  = 3
518!Config  Help = raideur du zoom en  X
519       tauxx = 3.0
520       CALL getin('taux',tauxx)
521
522      IF( fxyhypb )  THEN
523       IF( ABS(taux - tauxx).GE. 0.001 )  THEN
524        write(lunout,*)'conf_gcm: La valeur de taux passee par ',
525     * 'run.def est differente de celle lue sur le fichier  start '
526        STOP
527       ENDIF
528      ENDIF
529
530!Config  Key  = tauyy
531!Config  Desc = raideur du zoom en  Y
532!Config  Def  = 3
533!Config  Help = raideur du zoom en  Y
534       tauyy = 3.0
535       CALL getin('tauy',tauyy)
536
537      IF( fxyhypb )  THEN
538       IF( ABS(tauy - tauyy).GE. 0.001 )  THEN
539        write(lunout,*)'conf_gcm: La valeur de tauy passee par ',
540     * 'run.def est differente de celle lue sur le fichier  start '
541        STOP
542       ENDIF
543      ENDIF
544
545cc
546      IF( .NOT.fxyhypb  )  THEN
547
548!Config  Key  = ysinus
549!Config  IF   = !fxyhypb
550!Config  Desc = Fonction en Sinus
551!Config  Def  = y
552!Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
553!Config         sinon y = latit.
554       ysinuss = .TRUE.
555       CALL getin('ysinus',ysinuss)
556
557        IF( .NOT.ysinus )  THEN
558          IF( ysinuss )     THEN
559            write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
560            write(lunout,*)' *** ysinus lu sur le fichier start est F',
561     *       ' alors  qu il est  T  sur  run.def  ***'
562            STOP
563          ENDIF
564        ELSE
565          IF( .NOT.ysinuss )   THEN
566            write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
567            write(lunout,*)' *** ysinus lu sur le fichier start est T',
568     *        ' alors  qu il est  F  sur  run.def  ****  '
569              STOP
570          ENDIF
571        ENDIF
572      ENDIF ! of IF( .NOT.fxyhypb  )
573c
574!Config  Key  = offline
575!Config  Desc = Nouvelle eau liquide
576!Config  Def  = n
577!Config  Help = Permet de mettre en route la
578!Config         nouvelle parametrisation de l'eau liquide !
579       offline = .FALSE.
580       CALL getin('offline',offline)
581     
582!Config  Key  = type_trac
583!Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
584!Config  Def  = lmdz
585!Config  Help =
586!Config         'lmdz' = pas de couplage, pur LMDZ
587!Config         'inca' = model de chime INCA
588!Config         'repr' = model de chime REPROBUS
589      type_trac = 'lmdz'
590      CALL getin('type_trac',type_trac)
591
592!Config  Key  = config_inca
593!Config  Desc = Choix de configuration de INCA
594!Config  Def  = none
595!Config  Help = Choix de configuration de INCA :
596!Config         'none' = sans INCA
597!Config         'chem' = INCA avec calcul de chemie
598!Config         'aero' = INCA avec calcul des aerosols
599      config_inca = 'none'
600      CALL getin('config_inca',config_inca)
601
602!Config  Key  = ok_dynzon
603!Config  Desc = calcul et sortie des transports
604!Config  Def  = n
605!Config  Help = Permet de mettre en route le calcul des transports
606!Config         
607      ok_dynzon = .FALSE.
608      CALL getin('ok_dynzon',ok_dynzon)
609
610!Config  Key  = ok_dyn_ins
611!Config  Desc = sorties instantanees dans la dynamique
612!Config  Def  = n
613!Config  Help =
614!Config         
615      ok_dyn_ins = .FALSE.
616      CALL getin('ok_dyn_ins',ok_dyn_ins)
617
618!Config  Key  = ok_dyn_ave
619!Config  Desc = sorties moyennes dans la dynamique
620!Config  Def  = n
621!Config  Help =
622!Config         
623      ok_dyn_ave = .FALSE.
624      CALL getin('ok_dyn_ave',ok_dyn_ave)
625
626      write(lunout,*)' #########################################'
627      write(lunout,*)' Configuration des parametres du gcm: '
628      write(lunout,*)' planet_type = ', planet_type
629      write(lunout,*)' calend = ', calend
630      write(lunout,*)' dayref = ', dayref
631      write(lunout,*)' anneeref = ', anneeref
632      write(lunout,*)' nday = ', nday
633      write(lunout,*)' day_step = ', day_step
634      write(lunout,*)' iperiod = ', iperiod
635      write(lunout,*)' nsplit_phys = ', nsplit_phys
636      write(lunout,*)' iconser = ', iconser
637      write(lunout,*)' iecri = ', iecri
638      write(lunout,*)' periodav = ', periodav
639      write(lunout,*)' output_grads_dyn = ', output_grads_dyn
640      write(lunout,*)' dissip_period = ', dissip_period
641      write(lunout,*)' lstardis = ', lstardis
642      write(lunout,*)' nitergdiv = ', nitergdiv
643      write(lunout,*)' nitergrot = ', nitergrot
644      write(lunout,*)' niterh = ', niterh
645      write(lunout,*)' tetagdiv = ', tetagdiv
646      write(lunout,*)' tetagrot = ', tetagrot
647      write(lunout,*)' tetatemp = ', tetatemp
648      write(lunout,*)' coefdis = ', coefdis
649      write(lunout,*)' purmats = ', purmats
650      write(lunout,*)' read_start = ', read_start
651      write(lunout,*)' iflag_phys = ', iflag_phys
652      write(lunout,*)' iphysiq = ', iphysiq
653      write(lunout,*)' clonn = ', clonn
654      write(lunout,*)' clatt = ', clatt
655      write(lunout,*)' grossismx = ', grossismx
656      write(lunout,*)' grossismy = ', grossismy
657      write(lunout,*)' fxyhypbb = ', fxyhypbb
658      write(lunout,*)' dzoomxx = ', dzoomxx
659      write(lunout,*)' dzoomy = ', dzoomyy
660      write(lunout,*)' tauxx = ', tauxx
661      write(lunout,*)' tauyy = ', tauyy
662      write(lunout,*)' offline = ', offline
663      write(lunout,*)' type_trac = ', type_trac
664      write(lunout,*)' config_inca = ', config_inca
665      write(lunout,*)' ok_dynzon = ', ok_dynzon
666      write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
667      write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
668
669      RETURN
670c   ...............................................
671c
672100   CONTINUE
673!Config  Key  = clon
674!Config  Desc = centre du zoom, longitude
675!Config  Def  = 0
676!Config  Help = longitude en degres du centre
677!Config         du zoom
678       clon = 0.
679       CALL getin('clon',clon)
680
681!Config  Key  = clat
682!Config  Desc = centre du zoom, latitude
683!Config  Def  = 0
684!Config  Help = latitude en degres du centre du zoom
685!Config         
686       clat = 0.
687       CALL getin('clat',clat)
688
689!Config  Key  = grossismx
690!Config  Desc = zoom en longitude
691!Config  Def  = 1.0
692!Config  Help = facteur de grossissement du zoom,
693!Config         selon la longitude
694       grossismx = 1.0
695       CALL getin('grossismx',grossismx)
696
697!Config  Key  = grossismy
698!Config  Desc = zoom en latitude
699!Config  Def  = 1.0
700!Config  Help = facteur de grossissement du zoom,
701!Config         selon la latitude
702       grossismy = 1.0
703       CALL getin('grossismy',grossismy)
704
705      IF( grossismx.LT.1. )  THEN
706        write(lunout,*)
707     &   'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
708         STOP
709      ELSE
710         alphax = 1. - 1./ grossismx
711      ENDIF
712
713
714      IF( grossismy.LT.1. )  THEN
715        write(lunout,*)
716     &  'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
717         STOP
718      ELSE
719         alphay = 1. - 1./ grossismy
720      ENDIF
721
722      write(lunout,*)'conf_gcm: alphax alphay ',alphax,alphay
723c
724c    alphax et alphay sont les anciennes formulat. des grossissements
725c
726c
727
728!Config  Key  = fxyhypb
729!Config  Desc = Fonction  hyperbolique
730!Config  Def  = y
731!Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
732!Config         sinon  sinusoidale
733       fxyhypb = .TRUE.
734       CALL getin('fxyhypb',fxyhypb)
735
736!Config  Key  = dzoomx
737!Config  Desc = extension en longitude
738!Config  Def  = 0
739!Config  Help = extension en longitude  de la zone du zoom 
740!Config         ( fraction de la zone totale)
741       dzoomx = 0.0
742       CALL getin('dzoomx',dzoomx)
743
744!Config  Key  = dzoomy
745!Config  Desc = extension en latitude
746!Config  Def  = 0
747!Config  Help = extension en latitude de la zone  du zoom 
748!Config         ( fraction de la zone totale)
749       dzoomy = 0.0
750       CALL getin('dzoomy',dzoomy)
751
752!Config  Key  = taux
753!Config  Desc = raideur du zoom en  X
754!Config  Def  = 3
755!Config  Help = raideur du zoom en  X
756       taux = 3.0
757       CALL getin('taux',taux)
758
759!Config  Key  = tauy
760!Config  Desc = raideur du zoom en  Y
761!Config  Def  = 3
762!Config  Help = raideur du zoom en  Y
763       tauy = 3.0
764       CALL getin('tauy',tauy)
765
766!Config  Key  = ysinus
767!Config  IF   = !fxyhypb
768!Config  Desc = Fonction en Sinus
769!Config  Def  = y
770!Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
771!Config         sinon y = latit.
772       ysinus = .TRUE.
773       CALL getin('ysinus',ysinus)
774c
775!Config  Key  = offline
776!Config  Desc = Nouvelle eau liquide
777!Config  Def  = n
778!Config  Help = Permet de mettre en route la
779!Config         nouvelle parametrisation de l'eau liquide !
780       offline = .FALSE.
781       CALL getin('offline',offline)
782
783!Config  Key  = type_trac
784!Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
785!Config  Def  = lmdz
786!Config  Help =
787!Config         'lmdz' = pas de couplage, pur LMDZ
788!Config         'inca' = model de chime INCA
789!Config         'repr' = model de chime REPROBUS
790      type_trac = 'lmdz'
791      CALL getin('type_trac',type_trac)
792
793!Config  Key  = config_inca
794!Config  Desc = Choix de configuration de INCA
795!Config  Def  = none
796!Config  Help = Choix de configuration de INCA :
797!Config         'none' = sans INCA
798!Config         'chem' = INCA avec calcul de chemie
799!Config         'aero' = INCA avec calcul des aerosols
800      config_inca = 'none'
801      CALL getin('config_inca',config_inca)
802
803!Config  Key  = ok_dynzon
804!Config  Desc = sortie des transports zonaux dans la dynamique
805!Config  Def  = n
806!Config  Help = Permet de mettre en route le calcul des transports
807!Config         
808      ok_dynzon = .FALSE.
809      CALL getin('ok_dynzon',ok_dynzon)
810
811!Config  Key  = ok_dyn_ins
812!Config  Desc = sorties instantanees dans la dynamique
813!Config  Def  = n
814!Config  Help =
815!Config         
816      ok_dyn_ins = .FALSE.
817      CALL getin('ok_dyn_ins',ok_dyn_ins)
818
819!Config  Key  = ok_dyn_ave
820!Config  Desc = sorties moyennes dans la dynamique
821!Config  Def  = n
822!Config  Help =
823!Config         
824      ok_dyn_ave = .FALSE.
825      CALL getin('ok_dyn_ave',ok_dyn_ave)
826
827!Config  Key  = use_filtre_fft
828!Config  Desc = flag d'activation des FFT pour le filtre
829!Config  Def  = false
830!Config  Help = permet d'activer l'utilisation des FFT pour effectuer
831!Config         le filtrage aux poles.
832! Le filtre fft n'est pas implemente dans dyn3d
833      use_filtre_fft=.FALSE.
834      CALL getin('use_filtre_fft',use_filtre_fft)
835
836      IF (use_filtre_fft) THEN
837        write(lunout,*)'STOP !!!'
838        write(lunout,*)'use_filtre_fft n est pas implemente dans dyn3d'
839        STOP 1
840      ENDIF
841     
842!Config key = ok_strato
843!Config  Desc = activation de la version strato
844!Config  Def  = .FALSE.
845!Config  Help = active la version stratosphérique de LMDZ de F. Lott
846
847      ok_strato=.FALSE.
848      CALL getin('ok_strato',ok_strato)
849
850      vert_prof_dissip = merge(1, 0, ok_strato .and. llm==39)
851      CALL getin('vert_prof_dissip', vert_prof_dissip)
852      call assert(vert_prof_dissip == 0 .or. vert_prof_dissip ==  1,
853     $     "bad value for vert_prof_dissip")
854
855!Config  Key  = ok_gradsfile
856!Config  Desc = activation des sorties grads du guidage
857!Config  Def  = n
858!Config  Help = active les sorties grads du guidage
859
860       ok_gradsfile = .FALSE.
861       CALL getin('ok_gradsfile',ok_gradsfile)
862
863!Config  Key  = ok_limit
864!Config  Desc = creation des fichiers limit dans create_etat0_limit
865!Config  Def  = y
866!Config  Help = production du fichier limit.nc requise
867
868       ok_limit = .TRUE.
869       CALL getin('ok_limit',ok_limit)
870
871!Config  Key  = ok_etat0
872!Config  Desc = creation des fichiers etat0 dans create_etat0_limit
873!Config  Def  = y
874!Config  Help = production des fichiers start.nc, startphy.nc requise
875
876      ok_etat0 = .TRUE.
877      CALL getin('ok_etat0',ok_etat0)
878
879!Config  Key  = grilles_gcm_netcdf
880!Config  Desc = creation de fichier grilles_gcm.nc dans create_etat0_limit
881!Config  Def  = n
882      grilles_gcm_netcdf = .FALSE.
883      CALL getin('grilles_gcm_netcdf',grilles_gcm_netcdf)
884
885      write(lunout,*)' #########################################'
886      write(lunout,*)' Configuration des parametres de cel0'
887     &             //'_limit: '
888      write(lunout,*)' planet_type = ', planet_type
889      write(lunout,*)' calend = ', calend
890      write(lunout,*)' dayref = ', dayref
891      write(lunout,*)' anneeref = ', anneeref
892      write(lunout,*)' nday = ', nday
893      write(lunout,*)' day_step = ', day_step
894      write(lunout,*)' iperiod = ', iperiod
895      write(lunout,*)' iconser = ', iconser
896      write(lunout,*)' iecri = ', iecri
897      write(lunout,*)' periodav = ', periodav
898      write(lunout,*)' output_grads_dyn = ', output_grads_dyn
899      write(lunout,*)' dissip_period = ', dissip_period
900      write(lunout,*)' lstardis = ', lstardis
901      write(lunout,*)' nitergdiv = ', nitergdiv
902      write(lunout,*)' nitergrot = ', nitergrot
903      write(lunout,*)' niterh = ', niterh
904      write(lunout,*)' tetagdiv = ', tetagdiv
905      write(lunout,*)' tetagrot = ', tetagrot
906      write(lunout,*)' tetatemp = ', tetatemp
907      write(lunout,*)' coefdis = ', coefdis
908      write(lunout,*)' purmats = ', purmats
909      write(lunout,*)' read_start = ', read_start
910      write(lunout,*)' iflag_phys = ', iflag_phys
911      write(lunout,*)' iphysiq = ', iphysiq
912      write(lunout,*)' clon = ', clon
913      write(lunout,*)' clat = ', clat
914      write(lunout,*)' grossismx = ', grossismx
915      write(lunout,*)' grossismy = ', grossismy
916      write(lunout,*)' fxyhypb = ', fxyhypb
917      write(lunout,*)' dzoomx = ', dzoomx
918      write(lunout,*)' dzoomy = ', dzoomy
919      write(lunout,*)' taux = ', taux
920      write(lunout,*)' tauy = ', tauy
921      write(lunout,*)' offline = ', offline
922      write(lunout,*)' type_trac = ', type_trac
923      write(lunout,*)' config_inca = ', config_inca
924      write(lunout,*)' ok_dynzon = ', ok_dynzon
925      write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
926      write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
927      write(lunout,*)' ok_strato = ', ok_strato
928      write(lunout,*)' ok_gradsfile = ', ok_gradsfile
929      write(lunout,*)' ok_limit = ', ok_limit
930      write(lunout,*)' ok_etat0 = ', ok_etat0
931      write(lunout,*)' grilles_gcm_netcdf = ', grilles_gcm_netcdf
932c
933      RETURN
934      END
Note: See TracBrowser for help on using the repository browser.