source: LMDZ5/branches/testing/libf/dyn3d/conf_gcm.F90 @ 2275

Last change on this file since 2275 was 2258, checked in by Laurent Fairhead, 9 years ago

Merged trunk changes 2216:2237 into testing branch

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