source: LMDZ6/trunk/libf/dyn3dmem/conf_gcm.F90 @ 3006

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