source: LMDZ5/trunk/libf/dyn3dmem/conf_gcm.F90 @ 2444

Last change on this file since 2444 was 2444, checked in by Ehouarn Millour, 8 years ago

Bug fix: Enforcing (in parallel runs) the deactivation of the FFT filter for grids with a zoom in longitude was wrongly implemented.
EM

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