source: LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/conf_gcm.F @ 1141

Last change on this file since 1141 was 1140, checked in by Ehouarn Millour, 17 years ago

Premiere vaque de modifications pour l'unification des dynamiques (planetes-Terre) et un peu de netoyage ...

  • modified 'makegcm' and 'makegcm_fcm' to remove 'CPP_PHYS' key and add 'CPP_EARTH' preprocessing key instead
  • updated 'diagedyn.F' (in dyn3d and dyn3dpar) to use 'CPP_EARTH' key
  • added 'ioipsl_getincom.F90' and 'ioipsl_stringop.F90' to 'dyn3d' and 'dyn3dpar' for future possibility of running without IOIPSL library
  • modified conf_gcm.F ( in d'yn3d' and 'dyn3dpar') to read in flag 'planet_type' (default=='earth') (flag added in 'control.h')
  • modified 'gcm.F' (in 'dyn3d' and 'dyn3dpar') so that flags so that 'read_start' and 'iflag_phys' (known from conf_gcm.F) are used
  • added flag 'output_grads_dyn' (read by conf_gcm.F, stored in 'control.h') to write grads outputs from 'leapfrog.F' and 'leapfrog_p.F'
  • removed 'comdiss.h' from 'dyn3d' and 'dyn3dpar' (it is not used)
  • removed variable 'lstardis' from 'comdissip.h' (it is also in

'comdissnew.h'), in dyn3d as well as in dyn3dpar

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