source: LMDZ5/branches/LF-private/libf/dyn3d/conf_gcm.F @ 2942

Last change on this file since 2942 was 1793, checked in by Ehouarn Millour, 11 years ago

Improved sponge layer:

  • Sponge tendencies are now computed analytically, instead than using a Forward Euler approximation.
  • Sponge tendencies are added within top_bound, and the sponge is applied after physics tendencies have been taken into account.

These changes imply that GCM results (when using sponge layer) will be differentwrt bench test cases using previous revisions.
EM

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