source: trunk/LMDZ.COMMON/libf/dyn3dpar/conf_gcm.F90 @ 1443

Last change on this file since 1443 was 1441, checked in by emillour, 10 years ago

Updates in common dynamics (seq and ) to keep up with updates
in LMDZ5 (up to LMDZ5 trunk, rev 2250):

  • compilation:
  • added test in grid/dimension/makdim to check that # of longitudes is a multiple of 8
  • dyn3d_common:

Bug correction concerning zoom (cf LMDZ5 rev 2218)

  • coefpoly.F becomes coefpoly_m.F90 (in misc)
  • fxhyp.F => fxhyp_m.F90 , fyhyp.F => fyhyp_m.F90
  • new routines for zoom: invert_zoom_x_m.F90 and principal_cshift_m.F90
  • inigeom.F adapted to new zoom definition routines
  • fluxstokenc.F : got rid of calls to initial0()
  • dyn3d:
  • advtrac.F90 : got rid of calls to initial0()
  • conf_gcm.F90 : cosmetic changes and change in default dzoomx,dzoomy values
  • guide_mod.F90 : followed updates from Earth Model
  • gcm.F is now gcm.F90
  • dyn3dpar:
  • advtrac_p.F90, covcont_p.F90, mod_hallo.F90 : cosmetic changes
  • conf_gcm.F90 : cosmetic and changed in default dzoomx,dzoomy values
  • parallel_lmdz.F90 : updates to keep up with Earth model
  • misc:
  • arth.F90 becomes arth_m.F90
  • wxios.F90 updated wrt Earth model changes
  • nrtype.F90 and coefpoly_m.F90 added
  • ran1.F, sort.F, minmax.F, minmax2.F, juldate.F moved over from dyn3d_common

EM

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