source: LMDZ4/trunk/libf/dyn3d/conf_gcm.F @ 1418

Last change on this file since 1418 was 1418, checked in by jghattas, 14 years ago

Following bug corrections are already done at branch LMDZ4_AR5 rev
1417,1416 :

Bug corrections for nudged run (pres2lev.F90, guide_p_mod.F90) :

  • now the results are the same for sequentiel and parallel mode(if adjust=n and compiled with vsafe at mercure).
  • the results are the same as the sequential mode in previous revision.
  • test done only with guide_u=y,guide_v=y
  • copied optimized version of pres2lev.F90 from dyn3dpar to dyn3d


Added condition read_climoz for the variable O3daySTD(calcul_STDlev.h,
undefSTD.F)

Corrected bug in calculation of the diagnostic variable ec550aer
"Extinction at 550nm" (aeropt_5wv.F90) (Maria Raffaella Vuolo, LSCE)

Added stop if use_filtre_fft=y with dyn3d (conf_gcm.F) : this option is
not implemented in dyn3d.

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