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

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

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