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

Last change on this file since 5280 was 5280, checked in by abarral, 9 hours ago

Turn comdissip.h, comdissipn.h, comdissnew.h into modules

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