source: LMDZ5/trunk/libf/dyn3dmem/conf_gcm.F @ 1838

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

Remplacement de parallel.F90 (en conflit avec orchidée) par parallel_lmdz.F90.
UG
.........................................
Renaming parallel.F90 (conflicting with orchidée) into parallel_lmdz.F90.
UG

File size: 32.3 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_lmdz, 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! top_bound sponge: only active if ok_strato=.true. and iflag_top_bound!=0
338!                   iflag_top_bound=0 for no sponge
339!                   iflag_top_bound=1 for sponge over 4 topmost layers
340!                   iflag_top_bound=2 for sponge from top to ~1% of top layer pressure
341       iflag_top_bound=1
342       CALL getin('iflag_top_bound',iflag_top_bound)
343
344! mode_top_bound : fields towards which sponge relaxation will be done:
345!                  mode_top_bound=0: no relaxation
346!                  mode_top_bound=1: u and v relax towards 0
347!                  mode_top_bound=2: u and v relax towards their zonal mean
348!                  mode_top_bound=3: u,v and pot. temp. relax towards their zonal mean
349       mode_top_bound=3
350       CALL getin('mode_top_bound',mode_top_bound)
351
352! top_bound sponge : inverse of charactericstic relaxation time scale for sponge
353       tau_top_bound=1.e-5
354       CALL getin('tau_top_bound',tau_top_bound)
355
356!Config  Key  = coefdis
357!Config  Desc = coefficient pour gamdissip
358!Config  Def  = 0
359!Config  Help = coefficient pour gamdissip 
360       coefdis = 0.
361       CALL getin('coefdis',coefdis)
362
363!Config  Key  = purmats
364!Config  Desc = Schema d'integration
365!Config  Def  = n
366!Config  Help = Choix du schema d'integration temporel.
367!Config         y = pure Matsuno sinon c'est du Matsuno-leapfrog
368       purmats = .FALSE.
369       CALL getin('purmats',purmats)
370
371!Config  Key  = ok_guide
372!Config  Desc = Guidage
373!Config  Def  = n
374!Config  Help = Guidage
375       ok_guide = .FALSE.
376       CALL getin('ok_guide',ok_guide)
377
378c    ...............................................................
379
380!Config  Key  =  read_start
381!Config  Desc = Initialize model using a 'start.nc' file
382!Config  Def  = y
383!Config  Help = y: intialize dynamical fields using a 'start.nc' file
384!               n: fields are initialized by 'iniacademic' routine
385       read_start= .true.
386       CALL getin('read_start',read_start)
387
388!Config  Key  = iflag_phys
389!Config  Desc = Avec ls physique
390!Config  Def  = 1
391!Config  Help = Permet de faire tourner le modele sans
392!Config         physique.
393       iflag_phys = 1
394       CALL getin('iflag_phys',iflag_phys)
395
396
397!Config  Key  =  iphysiq
398!Config  Desc = Periode de la physique
399!Config  Def  = 5
400!Config  Help = Periode de la physique en pas de temps de la dynamique.
401       iphysiq = 5
402       CALL getin('iphysiq', iphysiq)
403
404!Config  Key  = ip_ebil_dyn
405!Config  Desc = PRINT level for energy conserv. diag.
406!Config  Def  = 0
407!Config  Help = PRINT level for energy conservation diag. ;
408!               les options suivantes existent :
409!Config         0 pas de print
410!Config         1 pas de print
411!Config         2 print,
412       ip_ebil_dyn = 0
413       CALL getin('ip_ebil_dyn',ip_ebil_dyn)
414!
415
416
417ccc  ....   P. Le Van , ajout  le 7/03/95 .pour le zoom ...
418c     .........   (  modif  le 17/04/96 )   .........
419c
420      IF( etatinit ) GO TO 100
421
422!Config  Key  = clon
423!Config  Desc = centre du zoom, longitude
424!Config  Def  = 0
425!Config  Help = longitude en degres du centre
426!Config         du zoom
427       clonn = 0.
428       CALL getin('clon',clonn)
429
430!Config  Key  = clat
431!Config  Desc = centre du zoom, latitude
432!Config  Def  = 0
433!Config  Help = latitude en degres du centre du zoom
434!Config         
435       clatt = 0.
436       CALL getin('clat',clatt)
437
438c
439c
440      IF( ABS(clat - clatt).GE. 0.001 )  THEN
441        write(lunout,*)'conf_gcm: La valeur de clat passee par run.def',
442     &    ' est differente de celle lue sur le fichier  start '
443        STOP
444      ENDIF
445
446!Config  Key  = grossismx
447!Config  Desc = zoom en longitude
448!Config  Def  = 1.0
449!Config  Help = facteur de grossissement du zoom,
450!Config         selon la longitude
451       grossismxx = 1.0
452       CALL getin('grossismx',grossismxx)
453
454
455      IF( ABS(grossismx - grossismxx).GE. 0.001 )  THEN
456        write(lunout,*)'conf_gcm: La valeur de grossismx passee par ',
457     &  'run.def est differente de celle lue sur le fichier  start '
458        STOP
459      ENDIF
460
461!Config  Key  = grossismy
462!Config  Desc = zoom en latitude
463!Config  Def  = 1.0
464!Config  Help = facteur de grossissement du zoom,
465!Config         selon la latitude
466       grossismyy = 1.0
467       CALL getin('grossismy',grossismyy)
468
469      IF( ABS(grossismy - grossismyy).GE. 0.001 )  THEN
470        write(lunout,*)'conf_gcm: La valeur de grossismy passee par ',
471     & 'run.def est differente de celle lue sur le fichier  start '
472        STOP
473      ENDIF
474     
475      IF( grossismx.LT.1. )  THEN
476        write(lunout,*)
477     &       'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
478         STOP
479      ELSE
480         alphax = 1. - 1./ grossismx
481      ENDIF
482
483
484      IF( grossismy.LT.1. )  THEN
485        write(lunout,*)
486     &       'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
487         STOP
488      ELSE
489         alphay = 1. - 1./ grossismy
490      ENDIF
491
492      write(lunout,*)'conf_gcm: alphax alphay',alphax,alphay
493c
494c    alphax et alphay sont les anciennes formulat. des grossissements
495c
496c
497
498!Config  Key  = fxyhypb
499!Config  Desc = Fonction  hyperbolique
500!Config  Def  = y
501!Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
502!Config         sinon  sinusoidale
503       fxyhypbb = .TRUE.
504       CALL getin('fxyhypb',fxyhypbb)
505
506      IF( .NOT.fxyhypb )  THEN
507         IF( fxyhypbb )     THEN
508            write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
509            write(lunout,*)' *** fxyhypb lu sur le fichier start est ',
510     *       'F alors  qu il est  T  sur  run.def  ***'
511              STOP
512         ENDIF
513      ELSE
514         IF( .NOT.fxyhypbb )   THEN
515            write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
516            write(lunout,*)' ***  fxyhypb lu sur le fichier start est ',
517     *        'T alors  qu il est  F  sur  run.def  ****  '
518              STOP
519         ENDIF
520      ENDIF
521c
522!Config  Key  = dzoomx
523!Config  Desc = extension en longitude
524!Config  Def  = 0
525!Config  Help = extension en longitude  de la zone du zoom 
526!Config         ( fraction de la zone totale)
527       dzoomxx = 0.0
528       CALL getin('dzoomx',dzoomxx)
529
530      IF( fxyhypb )  THEN
531       IF( ABS(dzoomx - dzoomxx).GE. 0.001 )  THEN
532        write(lunout,*)'conf_gcm: La valeur de dzoomx passee par ',
533     *  'run.def est differente de celle lue sur le fichier  start '
534        STOP
535       ENDIF
536      ENDIF
537
538!Config  Key  = dzoomy
539!Config  Desc = extension en latitude
540!Config  Def  = 0
541!Config  Help = extension en latitude de la zone  du zoom 
542!Config         ( fraction de la zone totale)
543       dzoomyy = 0.0
544       CALL getin('dzoomy',dzoomyy)
545
546      IF( fxyhypb )  THEN
547       IF( ABS(dzoomy - dzoomyy).GE. 0.001 )  THEN
548        write(lunout,*)'conf_gcm: La valeur de dzoomy passee par ',
549     * 'run.def est differente de celle lue sur le fichier  start '
550        STOP
551       ENDIF
552      ENDIF
553     
554!Config  Key  = taux
555!Config  Desc = raideur du zoom en  X
556!Config  Def  = 3
557!Config  Help = raideur du zoom en  X
558       tauxx = 3.0
559       CALL getin('taux',tauxx)
560
561      IF( fxyhypb )  THEN
562       IF( ABS(taux - tauxx).GE. 0.001 )  THEN
563        write(lunout,*)'conf_gcm: La valeur de taux passee par ',
564     * 'run.def est differente de celle lue sur le fichier  start '
565        STOP
566       ENDIF
567      ENDIF
568
569!Config  Key  = tauyy
570!Config  Desc = raideur du zoom en  Y
571!Config  Def  = 3
572!Config  Help = raideur du zoom en  Y
573       tauyy = 3.0
574       CALL getin('tauy',tauyy)
575
576      IF( fxyhypb )  THEN
577       IF( ABS(tauy - tauyy).GE. 0.001 )  THEN
578        write(lunout,*)'conf_gcm: La valeur de tauy passee par ',
579     * 'run.def est differente de celle lue sur le fichier  start '
580        STOP
581       ENDIF
582      ENDIF
583
584cc
585      IF( .NOT.fxyhypb  )  THEN
586
587!Config  Key  = ysinus
588!Config  IF   = !fxyhypb
589!Config  Desc = Fonction en Sinus
590!Config  Def  = y
591!Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
592!Config         sinon y = latit.
593       ysinuss = .TRUE.
594       CALL getin('ysinus',ysinuss)
595
596        IF( .NOT.ysinus )  THEN
597          IF( ysinuss )     THEN
598            write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
599            write(lunout,*)' *** ysinus lu sur le fichier start est F',
600     *       ' alors  qu il est  T  sur  run.def  ***'
601            STOP
602          ENDIF
603        ELSE
604          IF( .NOT.ysinuss )   THEN
605            write(lunout,*)' ********  PBS DANS  CONF_GCM  ******** '
606            write(lunout,*)' *** ysinus lu sur le fichier start est T',
607     *        ' alors  qu il est  F  sur  run.def  ****  '
608              STOP
609          ENDIF
610        ENDIF
611      ENDIF ! of IF( .NOT.fxyhypb  )
612c
613!Config  Key  = offline
614!Config  Desc = Nouvelle eau liquide
615!Config  Def  = n
616!Config  Help = Permet de mettre en route la
617!Config         nouvelle parametrisation de l'eau liquide !
618       offline = .FALSE.
619       CALL getin('offline',offline)
620       IF (offline .AND. adjust) THEN
621          WRITE(lunout,*)
622     &         'WARNING : option offline does not work with adjust=y :'
623          WRITE(lunout,*) 'the files defstoke.nc, fluxstoke.nc ',
624     &         'and fluxstokev.nc will not be created'
625          WRITE(lunout,*)
626     &         'only the file phystoke.nc will still be created '
627       END IF
628       
629!Config  Key  = type_trac
630!Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
631!Config  Def  = lmdz
632!Config  Help =
633!Config         'lmdz' = pas de couplage, pur LMDZ
634!Config         'inca' = model de chime INCA
635!Config         'repr' = model de chime REPROBUS
636      type_trac = 'lmdz'
637      CALL getin('type_trac',type_trac)
638
639!Config  Key  = config_inca
640!Config  Desc = Choix de configuration de INCA
641!Config  Def  = none
642!Config  Help = Choix de configuration de INCA :
643!Config         'none' = sans INCA
644!Config         'chem' = INCA avec calcul de chemie
645!Config         'aero' = INCA avec calcul des aerosols
646      config_inca = 'none'
647      CALL getin('config_inca',config_inca)
648
649!Config  Key  = ok_dynzon
650!Config  Desc = calcul et sortie des transports
651!Config  Def  = n
652!Config  Help = Permet de mettre en route le calcul des transports
653!Config         
654      ok_dynzon = .FALSE.
655      CALL getin('ok_dynzon',ok_dynzon)
656
657!Config  Key  = ok_dyn_ins
658!Config  Desc = sorties instantanees dans la dynamique
659!Config  Def  = n
660!Config  Help =
661!Config         
662      ok_dyn_ins = .FALSE.
663      CALL getin('ok_dyn_ins',ok_dyn_ins)
664
665!Config  Key  = ok_dyn_ave
666!Config  Desc = sorties moyennes dans la dynamique
667!Config  Def  = n
668!Config  Help =
669!Config         
670      ok_dyn_ave = .FALSE.
671      CALL getin('ok_dyn_ave',ok_dyn_ave)
672
673      write(lunout,*)' #########################################'
674      write(lunout,*)' Configuration des parametres du gcm: '
675      write(lunout,*)' planet_type = ', planet_type
676      write(lunout,*)' calend = ', calend
677      write(lunout,*)' dayref = ', dayref
678      write(lunout,*)' anneeref = ', anneeref
679      write(lunout,*)' nday = ', nday
680      write(lunout,*)' day_step = ', day_step
681      write(lunout,*)' iperiod = ', iperiod
682      write(lunout,*)' nsplit_phys = ', nsplit_phys
683      write(lunout,*)' iconser = ', iconser
684      write(lunout,*)' iecri = ', iecri
685      write(lunout,*)' periodav = ', periodav
686      write(lunout,*)' output_grads_dyn = ', output_grads_dyn
687      write(lunout,*)' dissip_period = ', dissip_period
688      write(lunout,*)' lstardis = ', lstardis
689      write(lunout,*)' nitergdiv = ', nitergdiv
690      write(lunout,*)' nitergrot = ', nitergrot
691      write(lunout,*)' niterh = ', niterh
692      write(lunout,*)' tetagdiv = ', tetagdiv
693      write(lunout,*)' tetagrot = ', tetagrot
694      write(lunout,*)' tetatemp = ', tetatemp
695      write(lunout,*)' coefdis = ', coefdis
696      write(lunout,*)' purmats = ', purmats
697      write(lunout,*)' read_start = ', read_start
698      write(lunout,*)' iflag_phys = ', iflag_phys
699      write(lunout,*)' iphysiq = ', iphysiq
700      write(lunout,*)' clonn = ', clonn
701      write(lunout,*)' clatt = ', clatt
702      write(lunout,*)' grossismx = ', grossismx
703      write(lunout,*)' grossismy = ', grossismy
704      write(lunout,*)' fxyhypbb = ', fxyhypbb
705      write(lunout,*)' dzoomxx = ', dzoomxx
706      write(lunout,*)' dzoomy = ', dzoomyy
707      write(lunout,*)' tauxx = ', tauxx
708      write(lunout,*)' tauyy = ', tauyy
709      write(lunout,*)' offline = ', offline
710      write(lunout,*)' type_trac = ', type_trac
711      write(lunout,*)' config_inca = ', config_inca
712      write(lunout,*)' ok_dynzon = ', ok_dynzon
713      write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
714      write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
715
716      RETURN
717c   ...............................................
718c
719100   CONTINUE
720!Config  Key  = clon
721!Config  Desc = centre du zoom, longitude
722!Config  Def  = 0
723!Config  Help = longitude en degres du centre
724!Config         du zoom
725       clon = 0.
726       CALL getin('clon',clon)
727
728!Config  Key  = clat
729!Config  Desc = centre du zoom, latitude
730!Config  Def  = 0
731!Config  Help = latitude en degres du centre du zoom
732!Config         
733       clat = 0.
734       CALL getin('clat',clat)
735
736!Config  Key  = grossismx
737!Config  Desc = zoom en longitude
738!Config  Def  = 1.0
739!Config  Help = facteur de grossissement du zoom,
740!Config         selon la longitude
741       grossismx = 1.0
742       CALL getin('grossismx',grossismx)
743
744!Config  Key  = grossismy
745!Config  Desc = zoom en latitude
746!Config  Def  = 1.0
747!Config  Help = facteur de grossissement du zoom,
748!Config         selon la latitude
749       grossismy = 1.0
750       CALL getin('grossismy',grossismy)
751
752      IF( grossismx.LT.1. )  THEN
753        write(lunout,*)
754     &   'conf_gcm: ***  ATTENTION !! grossismx < 1 .   *** '
755         STOP
756      ELSE
757         alphax = 1. - 1./ grossismx
758      ENDIF
759
760
761      IF( grossismy.LT.1. )  THEN
762        write(lunout,*)
763     &  'conf_gcm: ***  ATTENTION !! grossismy < 1 .   *** '
764         STOP
765      ELSE
766         alphay = 1. - 1./ grossismy
767      ENDIF
768
769      write(lunout,*)'conf_gcm: alphax alphay ',alphax,alphay
770c
771c    alphax et alphay sont les anciennes formulat. des grossissements
772c
773c
774
775!Config  Key  = fxyhypb
776!Config  Desc = Fonction  hyperbolique
777!Config  Def  = y
778!Config  Help = Fonction  f(y)  hyperbolique  si = .true. 
779!Config         sinon  sinusoidale
780       fxyhypb = .TRUE.
781       CALL getin('fxyhypb',fxyhypb)
782
783!Config  Key  = dzoomx
784!Config  Desc = extension en longitude
785!Config  Def  = 0
786!Config  Help = extension en longitude  de la zone du zoom 
787!Config         ( fraction de la zone totale)
788       dzoomx = 0.0
789       CALL getin('dzoomx',dzoomx)
790
791!Config  Key  = dzoomy
792!Config  Desc = extension en latitude
793!Config  Def  = 0
794!Config  Help = extension en latitude de la zone  du zoom 
795!Config         ( fraction de la zone totale)
796       dzoomy = 0.0
797       CALL getin('dzoomy',dzoomy)
798
799!Config  Key  = taux
800!Config  Desc = raideur du zoom en  X
801!Config  Def  = 3
802!Config  Help = raideur du zoom en  X
803       taux = 3.0
804       CALL getin('taux',taux)
805
806!Config  Key  = tauy
807!Config  Desc = raideur du zoom en  Y
808!Config  Def  = 3
809!Config  Help = raideur du zoom en  Y
810       tauy = 3.0
811       CALL getin('tauy',tauy)
812
813!Config  Key  = ysinus
814!Config  IF   = !fxyhypb
815!Config  Desc = Fonction en Sinus
816!Config  Def  = y
817!Config  Help = Fonction  f(y) avec y = Sin(latit.) si = .true.
818!Config         sinon y = latit.
819       ysinus = .TRUE.
820       CALL getin('ysinus',ysinus)
821c
822!Config  Key  = offline
823!Config  Desc = Nouvelle eau liquide
824!Config  Def  = n
825!Config  Help = Permet de mettre en route la
826!Config         nouvelle parametrisation de l'eau liquide !
827       offline = .FALSE.
828       CALL getin('offline',offline)
829       IF (offline .AND. adjust) THEN
830          WRITE(lunout,*)
831     &         'WARNING : option offline does not work with adjust=y :'
832          WRITE(lunout,*) 'the files defstoke.nc, fluxstoke.nc ',
833     &         'and fluxstokev.nc will not be created'
834          WRITE(lunout,*)
835     &         'only the file phystoke.nc will still be created '
836       END IF
837
838!Config  Key  = type_trac
839!Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
840!Config  Def  = lmdz
841!Config  Help =
842!Config         'lmdz' = pas de couplage, pur LMDZ
843!Config         'inca' = model de chime INCA
844!Config         'repr' = model de chime REPROBUS
845      type_trac = 'lmdz'
846      CALL getin('type_trac',type_trac)
847
848!Config  Key  = config_inca
849!Config  Desc = Choix de configuration de INCA
850!Config  Def  = none
851!Config  Help = Choix de configuration de INCA :
852!Config         'none' = sans INCA
853!Config         'chem' = INCA avec calcul de chemie
854!Config         'aero' = INCA avec calcul des aerosols
855      config_inca = 'none'
856      CALL getin('config_inca',config_inca)
857
858!Config  Key  = ok_dynzon
859!Config  Desc = sortie des transports zonaux dans la dynamique
860!Config  Def  = n
861!Config  Help = Permet de mettre en route le calcul des transports
862!Config         
863      ok_dynzon = .FALSE.
864      CALL getin('ok_dynzon',ok_dynzon)
865
866!Config  Key  = ok_dyn_ins
867!Config  Desc = sorties instantanees dans la dynamique
868!Config  Def  = n
869!Config  Help =
870!Config         
871      ok_dyn_ins = .FALSE.
872      CALL getin('ok_dyn_ins',ok_dyn_ins)
873
874!Config  Key  = ok_dyn_ave
875!Config  Desc = sorties moyennes dans la dynamique
876!Config  Def  = n
877!Config  Help =
878!Config         
879      ok_dyn_ave = .FALSE.
880      CALL getin('ok_dyn_ave',ok_dyn_ave)
881
882!Config  Key  = use_filtre_fft
883!Config  Desc = flag d'activation des FFT pour le filtre
884!Config  Def  = false
885!Config  Help = permet d'activer l'utilisation des FFT pour effectuer
886!Config         le filtrage aux poles.
887      use_filtre_fft=.FALSE.
888      CALL getin('use_filtre_fft',use_filtre_fft)
889      use_filtre_fft_loc=use_filtre_fft
890     
891      IF (use_filtre_fft .AND. grossismx /= 1.0) THEN
892        write(lunout,*)'WARNING !!! '
893        write(lunout,*)"Le zoom en longitude est incompatible",
894     &                 " avec l'utilisation du filtre FFT ",
895     &                 "---> FFT filter not active"
896       use_filtre_fft=.FALSE.
897      ENDIF
898     
899 
900     
901!Config  Key  = use_mpi_alloc
902!Config  Desc = Utilise un buffer MPI en m�moire globale
903!Config  Def  = false
904!Config  Help = permet d'activer l'utilisation d'un buffer MPI
905!Config         en m�moire globale a l'aide de la fonction MPI_ALLOC.
906!Config         Cela peut am�liorer la bande passante des transferts MPI
907!Config         d'un facteur 2 
908      use_mpi_alloc=.FALSE.
909      CALL getin('use_mpi_alloc',use_mpi_alloc)
910
911!Config  Key  = omp_chunk
912!Config  Desc = taille des blocs openmp
913!Config  Def  = 1
914!Config  Help = defini la taille des packets d'it�ration openmp
915!Config         distribu�e � chaque t�che lors de l'entr�e dans une
916!Config         boucle parall�lis�e
917 
918      omp_chunk=1
919      CALL getin('omp_chunk',omp_chunk)
920
921!Config key = ok_strato
922!Config  Desc = activation de la version strato
923!Config  Def  = .FALSE.
924!Config  Help = active la version stratosphérique de LMDZ de F. Lott
925
926      ok_strato=.FALSE.
927      CALL getin('ok_strato',ok_strato)
928
929      vert_prof_dissip = merge(1, 0, ok_strato .and. llm==39)
930      CALL getin('vert_prof_dissip', vert_prof_dissip)
931      call assert(vert_prof_dissip == 0 .or. vert_prof_dissip ==  1,
932     $     "bad value for vert_prof_dissip")
933
934!Config  Key  = ok_gradsfile
935!Config  Desc = activation des sorties grads du guidage
936!Config  Def  = n
937!Config  Help = active les sorties grads du guidage
938
939       ok_gradsfile = .FALSE.
940       CALL getin('ok_gradsfile',ok_gradsfile)
941
942!Config  Key  = ok_limit
943!Config  Desc = creation des fichiers limit dans create_etat0_limit
944!Config  Def  = y
945!Config  Help = production du fichier limit.nc requise
946
947       ok_limit = .TRUE.
948       CALL getin('ok_limit',ok_limit)
949
950!Config  Key  = ok_etat0
951!Config  Desc = creation des fichiers etat0 dans create_etat0_limit
952!Config  Def  = y
953!Config  Help = production des fichiers start.nc, startphy.nc requise
954
955      ok_etat0 = .TRUE.
956      CALL getin('ok_etat0',ok_etat0)
957
958!Config  Key  = grilles_gcm_netcdf
959!Config  Desc = creation de fichier grilles_gcm.nc dans create_etat0_limit
960!Config  Def  = n
961      grilles_gcm_netcdf = .FALSE.
962      CALL getin('grilles_gcm_netcdf',grilles_gcm_netcdf)
963
964      write(lunout,*)' #########################################'
965      write(lunout,*)' Configuration des parametres de cel0'
966     &             //'_limit: '
967      write(lunout,*)' planet_type = ', planet_type
968      write(lunout,*)' calend = ', calend
969      write(lunout,*)' dayref = ', dayref
970      write(lunout,*)' anneeref = ', anneeref
971      write(lunout,*)' nday = ', nday
972      write(lunout,*)' day_step = ', day_step
973      write(lunout,*)' iperiod = ', iperiod
974      write(lunout,*)' iconser = ', iconser
975      write(lunout,*)' iecri = ', iecri
976      write(lunout,*)' periodav = ', periodav
977      write(lunout,*)' output_grads_dyn = ', output_grads_dyn
978      write(lunout,*)' dissip_period = ', dissip_period
979      write(lunout,*)' lstardis = ', lstardis
980      write(lunout,*)' nitergdiv = ', nitergdiv
981      write(lunout,*)' nitergrot = ', nitergrot
982      write(lunout,*)' niterh = ', niterh
983      write(lunout,*)' tetagdiv = ', tetagdiv
984      write(lunout,*)' tetagrot = ', tetagrot
985      write(lunout,*)' tetatemp = ', tetatemp
986      write(lunout,*)' coefdis = ', coefdis
987      write(lunout,*)' purmats = ', purmats
988      write(lunout,*)' read_start = ', read_start
989      write(lunout,*)' iflag_phys = ', iflag_phys
990      write(lunout,*)' iphysiq = ', iphysiq
991      write(lunout,*)' clon = ', clon
992      write(lunout,*)' clat = ', clat
993      write(lunout,*)' grossismx = ', grossismx
994      write(lunout,*)' grossismy = ', grossismy
995      write(lunout,*)' fxyhypb = ', fxyhypb
996      write(lunout,*)' dzoomx = ', dzoomx
997      write(lunout,*)' dzoomy = ', dzoomy
998      write(lunout,*)' taux = ', taux
999      write(lunout,*)' tauy = ', tauy
1000      write(lunout,*)' offline = ', offline
1001      write(lunout,*)' type_trac = ', type_trac
1002      write(lunout,*)' config_inca = ', config_inca
1003      write(lunout,*)' ok_dynzon = ', ok_dynzon
1004      write(lunout,*)' ok_dyn_ins = ', ok_dyn_ins
1005      write(lunout,*)' ok_dyn_ave = ', ok_dyn_ave
1006      write(lunout,*)' use_filtre_fft = ', use_filtre_fft
1007      write(lunout,*)' use_mpi_alloc = ', use_mpi_alloc
1008      write(lunout,*)' omp_chunk = ', omp_chunk
1009      write(lunout,*)' ok_strato = ', ok_strato
1010      write(lunout,*)' ok_gradsfile = ', ok_gradsfile
1011      write(lunout,*)' ok_limit = ', ok_limit
1012      write(lunout,*)' ok_etat0 = ', ok_etat0
1013      write(lunout,*)' grilles_gcm_netcdf = ', grilles_gcm_netcdf
1014c
1015      RETURN
1016      END
Note: See TracBrowser for help on using the repository browser.