source: LMDZ4/branches/LMDZ4V5.0-dev/libf/dyn3dpar/conf_gcm.F @ 1357

Last change on this file since 1357 was 1357, checked in by Ehouarn Millour, 14 years ago

Some cleanup and fixing the possibility to output fields in the dynamics, on the dynamical grids.

CLEANUPS:

  • arch-PW6_VARGAS.fcm : add potentially benefic compiling options
  • removed obsolete "control.h" in dyn3d/dyn3dpar (module control_mod.F90 is used instead)

OUTPUTS in the dynamics (3 sets of files, one for each grid: scalar, u, v):

  • removed "com_io_dyn.h" common; use module "com_io_dyn_mod.F90" instead
  • updated "initdynav.F","inithist.F","writehist.F" and "writedynav.F" in bibio: which field will be written is hard coded there.
  • flags "ok_dyn_ins" and "ok_dyn_ave" (loaded via conf_gcm.F) trigger output of fields in the dynamics: if ok_dyn_ins is true, then files "dyn_hist.nc", "dyn_histu.nc" and "dyn_histv.nc" are written (the frequency of the outputs is given by 'iecri' in run.def; values are written every 'iecri' dynamical step). if ok_dyn_ave is true then files "dyn_hist_ave.nc", "dyn_histu_ave.nc" and "dyn_histv_ave.nc" are written (the rate at which averages and made/written, in days, is given by 'periodav' in run.def).

EM

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