source: LMDZ5/branches/LMDZ5-DOFOCO/libf/dyn3dpar/conf_gcm.F @ 2955

Last change on this file since 2955 was 1734, checked in by Ehouarn Millour, 11 years ago

Added test to stop if in OpenMP mode and trying to use adjust=y (which is not cleanly implemented); adjust=y should only be used in MPI mode (or in mixed MPI/OpenMP mode with only 1 thread).
EM

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