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

Last change on this file since 2143 was 2142, checked in by lguez, 10 years ago

dyn3d/conf_gcm.F, fixed source form, was included in lmdz1d.F90, free source
form, did not work. So converted conf_gcm.F to free source form. Also
converted dyn3dpar and dyn3dmem versions.

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