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

Last change on this file since 1279 was 1279, checked in by Laurent Fairhead, 15 years ago

Merged LMDZ4-dev branch changes r1241:1278 into the trunk
Running trunk and LMDZ4-dev in LMDZOR configuration on local
machine (sequential) and SX8 (4-proc) yields identical results
(restart and restartphy are identical binarily)
Log history from r1241 to r1278 is available by switching to
source:LMDZ4/branches/LMDZ4-dev-20091210

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 24.9 KB
Line 
1!
2! $Id: conf_gcm.F 1279 2009-12-10 09:02:56Z fairhead $
3!
4c
5c
6      SUBROUTINE conf_gcm( tapedef, etatinit, clesphy0 )
7c
8#ifdef CPP_IOIPSL
9      use IOIPSL
10#else
11! if not using IOIPSL, we still need to use (a local version of) getin
12      use ioipsl_getincom
13#endif
14      IMPLICIT NONE
15c-----------------------------------------------------------------------
16c     Auteurs :   L. Fairhead , P. Le Van  .
17c
18c     Arguments :
19c
20c     tapedef   :
21c     etatinit  :     = TRUE   , on ne  compare pas les valeurs des para-
22c     -metres  du zoom  avec  celles lues sur le fichier start .
23c      clesphy0 :  sortie  .
24c
25       LOGICAL etatinit
26       INTEGER tapedef
27
28       INTEGER        longcles
29       PARAMETER(     longcles = 20 )
30       REAL clesphy0( longcles )
31c
32c   Declarations :
33c   --------------
34#include "dimensions.h"
35#include "paramet.h"
36#include "control.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     
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  = iperiod
166!Config  Desc = periode pour le pas Matsuno
167!Config  Def  = 5
168!Config  Help = periode pour le pas Matsuno (en pas de temps)
169       iperiod = 5
170       CALL getin('iperiod',iperiod)
171
172!Config  Key  = iapp_tracvl
173!Config  Desc = frequence du groupement des flux
174!Config  Def  = iperiod
175!Config  Help = frequence du groupement des flux (en pas de temps)
176       iapp_tracvl = iperiod
177       CALL getin('iapp_tracvl',iapp_tracvl)
178
179!Config  Key  = iconser
180!Config  Desc = periode de sortie des variables de controle
181!Config  Def  = 240 
182!Config  Help = periode de sortie des variables de controle
183!Config         (En pas de temps)
184       iconser = 240 
185       CALL getin('iconser', iconser)
186
187!Config  Key  = iecri
188!Config  Desc = periode d'ecriture du fichier histoire
189!Config  Def  = 1
190!Config  Help = periode d'ecriture du fichier histoire (en jour)
191       iecri = 1
192       CALL getin('iecri',iecri)
193
194
195!Config  Key  = periodav
196!Config  Desc = periode de stockage fichier histmoy
197!Config  Def  = 1
198!Config  Help = periode de stockage fichier histmoy (en jour)
199       periodav = 1.
200       CALL getin('periodav',periodav)
201
202!Config  Key  = output_grads_dyn
203!Config  Desc = output dynamics diagnostics in 'dyn.dat' file
204!Config  Def  = n
205!Config  Help = output dynamics diagnostics in Grads-readable 'dyn.dat' file
206       output_grads_dyn=.false.
207       CALL getin('output_grads_dyn',output_grads_dyn)
208
209!Config  Key  = idissip
210!Config  Desc = periode de la dissipation
211!Config  Def  = 10
212!Config  Help = periode de la dissipation
213!Config         (en pas) ... a completer !
214       idissip = 10
215       CALL getin('idissip',idissip)
216
217ccc  ....   P. Le Van , modif le 29/04/97 .pour la dissipation  ...
218ccc
219
220!Config  Key  = lstardis
221!Config  Desc = choix de l'operateur de dissipation
222!Config  Def  = y
223!Config  Help = choix de l'operateur de dissipation
224!Config         'y' si on veut star et 'n' si on veut non-start !
225!Config         Moi y en a pas comprendre !
226       lstardis = .TRUE.
227       CALL getin('lstardis',lstardis)
228
229
230!Config  Key  = nitergdiv
231!Config  Desc = Nombre d'iteration de gradiv
232!Config  Def  = 1
233!Config  Help = nombre d'iterations de l'operateur de dissipation
234!Config         gradiv
235       nitergdiv = 1
236       CALL getin('nitergdiv',nitergdiv)
237
238!Config  Key  = nitergrot
239!Config  Desc = nombre d'iterations de nxgradrot
240!Config  Def  = 2
241!Config  Help = nombre d'iterations de l'operateur de dissipation 
242!Config         nxgradrot
243       nitergrot = 2
244       CALL getin('nitergrot',nitergrot)
245
246
247!Config  Key  = niterh
248!Config  Desc = nombre d'iterations de divgrad
249!Config  Def  = 2
250!Config  Help = nombre d'iterations de l'operateur de dissipation
251!Config         divgrad
252       niterh = 2
253       CALL getin('niterh',niterh)
254
255
256!Config  Key  = tetagdiv
257!Config  Desc = temps de dissipation pour div
258!Config  Def  = 7200
259!Config  Help = temps de dissipation des plus petites longeur
260!Config         d'ondes pour u,v (gradiv)
261       tetagdiv = 7200.
262       CALL getin('tetagdiv',tetagdiv)
263
264!Config  Key  = tetagrot
265!Config  Desc = temps de dissipation pour grad
266!Config  Def  = 7200
267!Config  Help = temps de dissipation des plus petites longeur
268!Config         d'ondes pour u,v (nxgradrot)
269       tetagrot = 7200.
270       CALL getin('tetagrot',tetagrot)
271
272!Config  Key  = tetatemp
273!Config  Desc = temps de dissipation pour h
274!Config  Def  = 7200
275!Config  Help =  temps de dissipation des plus petites longeur
276!Config         d'ondes pour h (divgrad)   
277       tetatemp  = 7200.
278       CALL getin('tetatemp',tetatemp )
279
280! Parametres controlant la variation sur la verticale des constantes de
281! dissipation.
282! Pour le moment actifs uniquement dans la version a 39 niveaux
283! avec ok_strato=y
284
285       dissip_factz=4.
286       dissip_deltaz=10.
287       dissip_zref=30.
288       CALL getin('dissip_factz',dissip_factz )
289       CALL getin('dissip_deltaz',dissip_deltaz )
290       CALL getin('dissip_zref',dissip_zref )
291
292       iflag_top_bound=1
293       tau_top_bound=1.e-5
294       CALL getin('iflag_top_bound',iflag_top_bound)
295       CALL getin('tau_top_bound',tau_top_bound)
296
297!Config  Key  = coefdis
298!Config  Desc = coefficient pour gamdissip
299!Config  Def  = 0
300!Config  Help = coefficient pour gamdissip 
301       coefdis = 0.
302       CALL getin('coefdis',coefdis)
303
304!Config  Key  = purmats
305!Config  Desc = Schema d'integration
306!Config  Def  = n
307!Config  Help = Choix du schema d'integration temporel.
308!Config         y = pure Matsuno sinon c'est du Matsuno-leapfrog
309       purmats = .FALSE.
310       CALL getin('purmats',purmats)
311
312!Config  Key  = ok_guide
313!Config  Desc = Guidage
314!Config  Def  = n
315!Config  Help = Guidage
316       ok_guide = .FALSE.
317       CALL getin('ok_guide',ok_guide)
318
319c    ...............................................................
320
321!Config  Key  =  read_start
322!Config  Desc = Initialize model using a 'start.nc' file
323!Config  Def  = y
324!Config  Help = y: intialize dynamical fields using a 'start.nc' file
325!               n: fields are initialized by 'iniacademic' routine
326       read_start= .true.
327       CALL getin('read_start',read_start)
328
329!Config  Key  = iflag_phys
330!Config  Desc = Avec ls physique
331!Config  Def  = 1
332!Config  Help = Permet de faire tourner le modele sans
333!Config         physique.
334       iflag_phys = 1
335       CALL getin('iflag_phys',iflag_phys)
336
337
338!Config  Key  =  iphysiq
339!Config  Desc = Periode de la physique
340!Config  Def  = 5
341!Config  Help = Periode de la physique en pas de temps de la dynamique.
342       iphysiq = 5
343       CALL getin('iphysiq', iphysiq)
344
345!Config  Key  = ip_ebil_dyn
346!Config  Desc = PRINT level for energy conserv. diag.
347!Config  Def  = 0
348!Config  Help = PRINT level for energy conservation diag. ;
349!               les options suivantes existent :
350!Config         0 pas de print
351!Config         1 pas de print
352!Config         2 print,
353       ip_ebil_dyn = 0
354       CALL getin('ip_ebil_dyn',ip_ebil_dyn)
355!
356
357      DO i = 1, longcles
358       clesphy0(i) = 0.
359      ENDDO
360
361ccc  ....   P. Le Van , ajout  le 7/03/95 .pour le zoom ...
362c     .........   (  modif  le 17/04/96 )   .........
363c
364      IF( etatinit ) GO TO 100
365
366!Config  Key  = clon
367!Config  Desc = centre du zoom, longitude
368!Config  Def  = 0
369!Config  Help = longitude en degres du centre
370!Config         du zoom
371       clonn = 0.
372       CALL getin('clon',clonn)
373
374!Config  Key  = clat
375!Config  Desc = centre du zoom, latitude
376!Config  Def  = 0
377!Config  Help = latitude en degres du centre du zoom
378!Config         
379       clatt = 0.
380       CALL getin('clat',clatt)
381
382c
383c
384      IF( ABS(clat - clatt).GE. 0.001 )  THEN
385        write(lunout,*)'conf_gcm: La valeur de clat passee par run.def',
386     &    ' est differente de celle lue sur le fichier  start '
387        STOP
388      ENDIF
389
390!Config  Key  = grossismx
391!Config  Desc = zoom en longitude
392!Config  Def  = 1.0
393!Config  Help = facteur de grossissement du zoom,
394!Config         selon la longitude
395       grossismxx = 1.0
396       CALL getin('grossismx',grossismxx)
397
398
399      IF( ABS(grossismx - grossismxx).GE. 0.001 )  THEN
400        write(lunout,*)'conf_gcm: La valeur de grossismx passee par ',
401     &  'run.def est differente de celle lue sur le fichier  start '
402        STOP
403      ENDIF
404
405!Config  Key  = grossismy
406!Config  Desc = zoom en latitude
407!Config  Def  = 1.0
408!Config  Help = facteur de grossissement du zoom,
409!Config         selon la latitude
410       grossismyy = 1.0
411       CALL getin('grossismy',grossismyy)
412
413      IF( ABS(grossismy - grossismyy).GE. 0.001 )  THEN
414        write(lunout,*)'conf_gcm: La valeur de grossismy passee par ',
415     & 'run.def est differente de celle lue sur le fichier  start '
416        STOP
417      ENDIF
418     
419      IF( grossismx.LT.1. )  THEN
420        write(lunout,*)
421     &       'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
422         STOP
423      ELSE
424         alphax = 1. - 1./ grossismx
425      ENDIF
426
427
428      IF( grossismy.LT.1. )  THEN
429        write(lunout,*)
430     &       'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
431         STOP
432      ELSE
433         alphay = 1. - 1./ grossismy
434      ENDIF
435
436      write(lunout,*)'conf_gcm: alphax alphay',alphax,alphay
437c
438c    alphax et alphay sont les anciennes formulat. des grossissements
439c
440c
441
442!Config  Key  = fxyhypb
443!Config  Desc = Fonction  hyperbolique
444!Config  Def  = y
445!Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
446!Config         sinon  sinusoidale
447       fxyhypbb = .TRUE.
448       CALL getin('fxyhypb',fxyhypbb)
449
450      IF( .NOT.fxyhypb )  THEN
451         IF( fxyhypbb )     THEN
452            write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
453            write(lunout,*)' *** fxyhypb lu sur le fichier start est ',
454     *       'F alors  qu il est  T  sur  run.def  ***'
455              STOP
456         ENDIF
457      ELSE
458         IF( .NOT.fxyhypbb )   THEN
459            write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
460            write(lunout,*)' ***  fxyhypb lu sur le fichier start est ',
461     *        'T alors  qu il est  F  sur  run.def  ****  '
462              STOP
463         ENDIF
464      ENDIF
465c
466!Config  Key  = dzoomx
467!Config  Desc = extension en longitude
468!Config  Def  = 0
469!Config  Help = extension en longitude  de la zone du zoom 
470!Config         ( fraction de la zone totale)
471       dzoomxx = 0.0
472       CALL getin('dzoomx',dzoomxx)
473
474      IF( fxyhypb )  THEN
475       IF( ABS(dzoomx - dzoomxx).GE. 0.001 )  THEN
476        write(lunout,*)'conf_gcm: La valeur de dzoomx passee par ',
477     *  'run.def est differente de celle lue sur le fichier  start '
478        STOP
479       ENDIF
480      ENDIF
481
482!Config  Key  = dzoomy
483!Config  Desc = extension en latitude
484!Config  Def  = 0
485!Config  Help = extension en latitude de la zone  du zoom 
486!Config         ( fraction de la zone totale)
487       dzoomyy = 0.0
488       CALL getin('dzoomy',dzoomyy)
489
490      IF( fxyhypb )  THEN
491       IF( ABS(dzoomy - dzoomyy).GE. 0.001 )  THEN
492        write(lunout,*)'conf_gcm: La valeur de dzoomy passee par ',
493     * 'run.def est differente de celle lue sur le fichier  start '
494        STOP
495       ENDIF
496      ENDIF
497     
498!Config  Key  = taux
499!Config  Desc = raideur du zoom en  X
500!Config  Def  = 3
501!Config  Help = raideur du zoom en  X
502       tauxx = 3.0
503       CALL getin('taux',tauxx)
504
505      IF( fxyhypb )  THEN
506       IF( ABS(taux - tauxx).GE. 0.001 )  THEN
507        write(lunout,*)'conf_gcm: La valeur de taux passee par ',
508     * 'run.def est differente de celle lue sur le fichier  start '
509        STOP
510       ENDIF
511      ENDIF
512
513!Config  Key  = tauyy
514!Config  Desc = raideur du zoom en  Y
515!Config  Def  = 3
516!Config  Help = raideur du zoom en  Y
517       tauyy = 3.0
518       CALL getin('tauy',tauyy)
519
520      IF( fxyhypb )  THEN
521       IF( ABS(tauy - tauyy).GE. 0.001 )  THEN
522        write(lunout,*)'conf_gcm: La valeur de tauy passee par ',
523     * 'run.def est differente de celle lue sur le fichier  start '
524        STOP
525       ENDIF
526      ENDIF
527
528cc
529      IF( .NOT.fxyhypb  )  THEN
530
531!Config  Key  = ysinus
532!Config  IF   = !fxyhypb
533!Config  Desc = Fonction en Sinus
534!Config  Def  = y
535!Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
536!Config         sinon y = latit.
537       ysinuss = .TRUE.
538       CALL getin('ysinus',ysinuss)
539
540        IF( .NOT.ysinus )  THEN
541          IF( ysinuss )     THEN
542            write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
543            write(lunout,*)' *** ysinus lu sur le fichier start est F',
544     *       ' alors  qu il est  T  sur  run.def  ***'
545            STOP
546          ENDIF
547        ELSE
548          IF( .NOT.ysinuss )   THEN
549            write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
550            write(lunout,*)' *** ysinus lu sur le fichier start est T',
551     *        ' alors  qu il est  F  sur  run.def  ****  '
552              STOP
553          ENDIF
554        ENDIF
555      ENDIF ! of IF( .NOT.fxyhypb  )
556c
557!Config  Key  = offline
558!Config  Desc = Nouvelle eau liquide
559!Config  Def  = n
560!Config  Help = Permet de mettre en route la
561!Config         nouvelle parametrisation de l'eau liquide !
562       offline = .FALSE.
563       CALL getin('offline',offline)
564
565!Config  Key  = config_inca
566!Config  Desc = Choix de configuration de INCA
567!Config  Def  = none
568!Config  Help = Choix de configuration de INCA :
569!Config         'none' = sans INCA
570!Config         'chem' = INCA avec calcul de chemie
571!Config         'aero' = INCA avec calcul des aerosols
572      config_inca = 'none'
573      CALL getin('config_inca',config_inca)
574
575
576!Config  Key  = ok_dynzon
577!Config  Desc = calcul et sortie des transports
578!Config  Def  = n
579!Config  Help = Permet de mettre en route le calcul des transports
580!Config         
581      ok_dynzon = .FALSE.
582      CALL getin('ok_dynzon',ok_dynzon)
583
584      write(lunout,*)' #########################################'
585      write(lunout,*)' Configuration des parametres du gcm: '
586      write(lunout,*)' planet_type = ', planet_type
587      write(lunout,*)' calend = ', calend
588      write(lunout,*)' dayref = ', dayref
589      write(lunout,*)' anneeref = ', anneeref
590      write(lunout,*)' nday = ', nday
591      write(lunout,*)' day_step = ', day_step
592      write(lunout,*)' iperiod = ', iperiod
593      write(lunout,*)' iconser = ', iconser
594      write(lunout,*)' iecri = ', iecri
595      write(lunout,*)' periodav = ', periodav
596      write(lunout,*)' output_grads_dyn = ', output_grads_dyn
597      write(lunout,*)' idissip = ', idissip
598      write(lunout,*)' lstardis = ', lstardis
599      write(lunout,*)' nitergdiv = ', nitergdiv
600      write(lunout,*)' nitergrot = ', nitergrot
601      write(lunout,*)' niterh = ', niterh
602      write(lunout,*)' tetagdiv = ', tetagdiv
603      write(lunout,*)' tetagrot = ', tetagrot
604      write(lunout,*)' tetatemp = ', tetatemp
605      write(lunout,*)' coefdis = ', coefdis
606      write(lunout,*)' purmats = ', purmats
607      write(lunout,*)' read_start = ', read_start
608      write(lunout,*)' iflag_phys = ', iflag_phys
609      write(lunout,*)' iphysiq = ', iphysiq
610      write(lunout,*)' clonn = ', clonn
611      write(lunout,*)' clatt = ', clatt
612      write(lunout,*)' grossismx = ', grossismx
613      write(lunout,*)' grossismy = ', grossismy
614      write(lunout,*)' fxyhypbb = ', fxyhypbb
615      write(lunout,*)' dzoomxx = ', dzoomxx
616      write(lunout,*)' dzoomy = ', dzoomyy
617      write(lunout,*)' tauxx = ', tauxx
618      write(lunout,*)' tauyy = ', tauyy
619      write(lunout,*)' offline = ', offline
620      write(lunout,*)' config_inca = ', config_inca
621      write(lunout,*)' ok_dynzon = ', ok_dynzon
622
623      RETURN
624c   ...............................................
625c
626100   CONTINUE
627!Config  Key  = clon
628!Config  Desc = centre du zoom, longitude
629!Config  Def  = 0
630!Config  Help = longitude en degres du centre
631!Config         du zoom
632       clon = 0.
633       CALL getin('clon',clon)
634
635!Config  Key  = clat
636!Config  Desc = centre du zoom, latitude
637!Config  Def  = 0
638!Config  Help = latitude en degres du centre du zoom
639!Config         
640       clat = 0.
641       CALL getin('clat',clat)
642
643!Config  Key  = grossismx
644!Config  Desc = zoom en longitude
645!Config  Def  = 1.0
646!Config  Help = facteur de grossissement du zoom,
647!Config         selon la longitude
648       grossismx = 1.0
649       CALL getin('grossismx',grossismx)
650
651!Config  Key  = grossismy
652!Config  Desc = zoom en latitude
653!Config  Def  = 1.0
654!Config  Help = facteur de grossissement du zoom,
655!Config         selon la latitude
656       grossismy = 1.0
657       CALL getin('grossismy',grossismy)
658
659      IF( grossismx.LT.1. )  THEN
660        write(lunout,*)
661     &   'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
662         STOP
663      ELSE
664         alphax = 1. - 1./ grossismx
665      ENDIF
666
667
668      IF( grossismy.LT.1. )  THEN
669        write(lunout,*)
670     &  'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
671         STOP
672      ELSE
673         alphay = 1. - 1./ grossismy
674      ENDIF
675
676      write(lunout,*)'conf_gcm: alphax alphay ',alphax,alphay
677c
678c    alphax et alphay sont les anciennes formulat. des grossissements
679c
680c
681
682!Config  Key  = fxyhypb
683!Config  Desc = Fonction  hyperbolique
684!Config  Def  = y
685!Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
686!Config         sinon  sinusoidale
687       fxyhypb = .TRUE.
688       CALL getin('fxyhypb',fxyhypb)
689
690!Config  Key  = dzoomx
691!Config  Desc = extension en longitude
692!Config  Def  = 0
693!Config  Help = extension en longitude  de la zone du zoom 
694!Config         ( fraction de la zone totale)
695       dzoomx = 0.0
696       CALL getin('dzoomx',dzoomx)
697
698!Config  Key  = dzoomy
699!Config  Desc = extension en latitude
700!Config  Def  = 0
701!Config  Help = extension en latitude de la zone  du zoom 
702!Config         ( fraction de la zone totale)
703       dzoomy = 0.0
704       CALL getin('dzoomy',dzoomy)
705
706!Config  Key  = taux
707!Config  Desc = raideur du zoom en  X
708!Config  Def  = 3
709!Config  Help = raideur du zoom en  X
710       taux = 3.0
711       CALL getin('taux',taux)
712
713!Config  Key  = tauy
714!Config  Desc = raideur du zoom en  Y
715!Config  Def  = 3
716!Config  Help = raideur du zoom en  Y
717       tauy = 3.0
718       CALL getin('tauy',tauy)
719
720!Config  Key  = ysinus
721!Config  IF   = !fxyhypb
722!Config  Desc = Fonction en Sinus
723!Config  Def  = y
724!Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
725!Config         sinon y = latit.
726       ysinus = .TRUE.
727       CALL getin('ysinus',ysinus)
728c
729!Config  Key  = offline
730!Config  Desc = Nouvelle eau liquide
731!Config  Def  = n
732!Config  Help = Permet de mettre en route la
733!Config         nouvelle parametrisation de l'eau liquide !
734       offline = .FALSE.
735       CALL getin('offline',offline)
736
737!Config  Key  = config_inca
738!Config  Desc = Choix de configuration de INCA
739!Config  Def  = none
740!Config  Help = Choix de configuration de INCA :
741!Config         'none' = sans INCA
742!Config         'chem' = INCA avec calcul de chemie
743!Config         'aero' = INCA avec calcul des aerosols
744      config_inca = 'none'
745      CALL getin('config_inca',config_inca)
746
747!Config  Key  = ok_dynzon
748!Config  Desc = calcul et sortie des transports
749!Config  Def  = n
750!Config  Help = Permet de mettre en route le calcul des transports
751!Config         
752       ok_dynzon = .FALSE.
753       CALL getin('ok_dynzon',ok_dynzon)
754
755!Config key = ok_strato
756!Config  Desc = activation de la version strato
757!Config  Def  = .FALSE.
758!Config  Help = active la version stratosphérique de LMDZ de F. Lott
759
760      ok_strato=.FALSE.
761      CALL getin('ok_strato',ok_strato)
762
763!Config  Key  = ok_gradsfile
764!Config  Desc = activation des sorties grads du guidage
765!Config  Def  = n
766!Config  Help = active les sorties grads du guidage
767
768       ok_gradsfile = .FALSE.
769       CALL getin('ok_gradsfile',ok_gradsfile)
770
771      write(lunout,*)' #########################################'
772      write(lunout,*)' Configuration des parametres du gcm: '
773      write(lunout,*)' planet_type = ', planet_type
774      write(lunout,*)' calend = ', calend
775      write(lunout,*)' dayref = ', dayref
776      write(lunout,*)' anneeref = ', anneeref
777      write(lunout,*)' nday = ', nday
778      write(lunout,*)' day_step = ', day_step
779      write(lunout,*)' iperiod = ', iperiod
780      write(lunout,*)' iconser = ', iconser
781      write(lunout,*)' iecri = ', iecri
782      write(lunout,*)' periodav = ', periodav
783      write(lunout,*)' output_grads_dyn = ', output_grads_dyn
784      write(lunout,*)' idissip = ', idissip
785      write(lunout,*)' lstardis = ', lstardis
786      write(lunout,*)' nitergdiv = ', nitergdiv
787      write(lunout,*)' nitergrot = ', nitergrot
788      write(lunout,*)' niterh = ', niterh
789      write(lunout,*)' tetagdiv = ', tetagdiv
790      write(lunout,*)' tetagrot = ', tetagrot
791      write(lunout,*)' tetatemp = ', tetatemp
792      write(lunout,*)' coefdis = ', coefdis
793      write(lunout,*)' purmats = ', purmats
794      write(lunout,*)' read_start = ', read_start
795      write(lunout,*)' iflag_phys = ', iflag_phys
796      write(lunout,*)' iphysiq = ', iphysiq
797      write(lunout,*)' clon = ', clon
798      write(lunout,*)' clat = ', clat
799      write(lunout,*)' grossismx = ', grossismx
800      write(lunout,*)' grossismy = ', grossismy
801      write(lunout,*)' fxyhypb = ', fxyhypb
802      write(lunout,*)' dzoomx = ', dzoomx
803      write(lunout,*)' dzoomy = ', dzoomy
804      write(lunout,*)' taux = ', taux
805      write(lunout,*)' tauy = ', tauy
806      write(lunout,*)' offline = ', offline
807      write(lunout,*)' config_inca = ', config_inca
808      write(lunout,*)' ok_dynzon = ', ok_dynzon
809      write(lunout,*)' ok_strato = ', ok_strato
810      write(lunout,*)' ok_gradsfile = ', ok_gradsfile
811c
812      RETURN
813      END
Note: See TracBrowser for help on using the repository browser.