source: LMDZ5/branches/testing/libf/dyn3dmem/conf_gcm.F @ 1790

Last change on this file since 1790 was 1750, checked in by Laurent Fairhead, 11 years ago

Version testing basée sur r1745


Testing release based on r1745

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