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

Last change on this file since 3579 was 3579, checked in by Laurent Fairhead, 5 years ago

Make aquaplanets run again (on jean-zay)
EM & MP

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