source: trunk/LMDZ.VENUS/libf/phyvenus/conf_phys.F90 @ 3094

Last change on this file since 3094 was 3035, checked in by amartinez, 16 months ago

======= VENUS PCM ===============

COMMIT BY ANTOINE MARTINEZ

Implementation of vertical ambipolar diffusion in physics

=================================

NEW KEYWORD OF PHYSIQ.DEF

=================================

NEW VERSION OF "physiq.def"

  • deftank/physiq-96x96x90-chemistry-IONOSPHERE-IONDIFF.def
  • ok_iondiff: keyword supposed to activate ion ambipolar diffusion
  • nbapp_chem: replaces nbapp_chim, in order to characterize the Number of calls to the chemistry routines (per Venusian day)

================

phyvenus

================

Iondiff_red.F

  • Calculation of the Ion Ambipolar Diffusion for 13 ions on 14:

O2+, O+, C+, N+, CO2+,
NO+, CO+, H+, H2O+, H3O+,

HCO+, N2+, OH+


The ion temperature is fixed as the half of the electron temperature
calculated in ion_h.F for the stability of the program and because the
ion temperature is lower than electron temperature.

plasmaphys_venus_mod.F90

  • parameters of the ambipolar diffusion scheme:

parameter (Pdiffion = 7.0D-4) ! pressure in Pa below which ion diffusion is computed
parameter (naltvert = 168) ! number of level on the altimetric subgrid
parameter (nsubvert = 24000) ! ptimephysiq/nsubvert - minimum sub-timestep allowed
parameter ( nsubmin = 40) ! ptimephysiq/nsubmin - maximum sub-timestep allowed

physic_mod.F

  • nbapp_chem is not fixed anymore here but deftank/in physiq.def
  • Ambipolar diffusion activated if (ok_iondiff) is true

conf_phys.f90

  • add ok_iondiff as parameters to read from physiq.def file set to .false. by default
  • add nbapp_chem as parameters to characterize the Number of calls to the chemistry routines (per Venusian day) instead of be fixed in physic_mod.F

to read from physiq.def file set to 24000 by default

cleshphys.h

  • added ok_iondiff & nbapp_chem in COMMON/clesphys_l/
  • removed nbapp_chim

phytrac_chemistry.F

  • Added security in the calculation of the sza_local in order to avoid the rare case where the |range| is above 1
File size: 14.1 KB
Line 
1!
2! $Header: /home/cvsroot/LMDZ4/libf/phylmd/conf_phys.F90,v 1.3 2005/02/07 15:15:31 fairhead Exp $
3!
4!
5!
6
7  subroutine conf_phys(ok_journe, ok_mensuel, ok_instan, &
8 &                     if_ebil)
9   use init_print_control_mod, only: init_print_control
10   use print_control_mod, only: lunout
11   use IOIPSL, only: getin
12
13   implicit none
14
15   include "YOMCST.h"
16   include "clesphys.h"
17   include "compbl.h"
18
19! ok_journe:  sorties journalieres
20! ok_mensuel: sorties mensuelles
21! ok_instan:  sorties instantanees
22
23
24! Sortie:
25  logical,intent(out)  :: ok_journe, ok_mensuel, ok_instan       
26  integer,intent(out)  :: if_ebil
27
28
29
30!
31! Configuration de la "physique" de LMDZ a l'aide de la fonction
32! GETIN de IOIPSL
33!
34! LF 05/2001
35!
36!--- Ca lit le physiq.def ---
37
38       ! initialize print_control module variables
39       call init_print_control
40
41!******************* parametres anciennement lus dans gcm.def
42
43       ! do we read a startphy.nc file? (default: .true.)
44       startphy_file=.true.
45       CALL getin("startphy_file",startphy_file)
46
47!Config  Key  = cycle_diurne
48!Config  Desc = Cycle diurne
49!Config  Def  = y
50!Config  Help = Cette option permet d'eteidre le cycle diurne.
51!Config         Peut etre util pour accelerer le code !
52       cycle_diurne = .TRUE.       
53       call getin('cycle_diurne',cycle_diurne)
54
55!Config  Key  = soil_model
56!Config  Desc = Modele de sol
57!Config  Def  = y
58!Config  Help = Choix du modele de sol (Thermique ?)
59!Config         Option qui pourait un string afin de pouvoir
60!Config         plus de choix ! Ou meme une liste d'options !
61       soil_model = .true.
62       call getin('soil_model',soil_model)
63
64!Config  Key  = ok_orodr
65!Config  Desc = Oro drag
66!Config  Def  = y
67!Config  Help = GW drag orographie
68!Config         
69       ok_orodr = .false.
70       call getin('ok_orodr',ok_orodr)
71
72!Config  Key  =  ok_orolf
73!Config  Desc = Oro lift
74!Config  Def  = n
75!Config  Help = GW lift orographie (pas utilise)
76       ok_orolf = .false.
77       call getin('ok_orolf', ok_orolf)
78
79!Config  Key  = ok_gw_nonoro
80!Config  Desc = Gravity waves parameterization
81!Config  Def  = n
82!Config  Help = GW drag non-orographique
83       ok_gw_nonoro = .false.
84       call getin('ok_gw_nonoro',ok_gw_nonoro)
85
86!Config  Key  = nbapp_rad
87!Config  Desc = Frequence d'appel au rayonnement
88!Config  Def  = 12
89!Config  Help = Nombre  d'appels des routines de rayonnements
90!Config         par jour.
91       nbapp_rad = 12
92       call getin('nbapp_rad',nbapp_rad)
93       print*,"nbapp_rad",nbapp_rad
94!Config  Key  = nbapp_chem
95!Config  Desc = Frequence d'appel a la chimie
96!Config  Def  = 24000
97!Config  Help = Nombre  d'appels des routines de chimie
98!Config         par jour.
99       nbapp_chem = 24000
100       call getin('nbapp_chem',nbapp_chem)
101
102!Config  Key  = iflag_con
103!Config  Desc = Flag de convection
104!Config  Def  = 0
105!Config  Help = Flag  pour la convection les options suivantes existent :
106!Config         0 : ajsec simple (VENUS, TITAN)
107!Config         1 pour LMD,
108!Config         2 pour Tiedtke,
109!Config         3 pour CCM(NCAR) 
110       iflag_con = 0
111       call getin('iflag_con',iflag_con)
112
113!******************* fin parametres anciennement lus dans gcm.def
114
115!Config Key  = OK_journe
116!Config Desc = Pour des sorties journalieres
117!Config Def  = .false.
118!Config Help = Pour creer le fichier histday contenant les sorties
119!              journalieres
120!
121  ok_journe = .false.
122  call getin('OK_journe', ok_journe)
123!
124!Config Key  = OK_mensuel
125!Config Desc = Pour des sorties mensuelles
126!Config Def  = .false.
127!Config Help = Pour creer le fichier histmth contenant les sorties
128!              mensuelles
129!
130  ok_mensuel = .false.
131  call getin('OK_mensuel', ok_mensuel)
132!
133!Config Key  = OK_instan
134!Config Desc = Pour des sorties instantanees
135!Config Def  = .false.
136!Config Help = Pour creer le fichier histins contenant les sorties
137!              instantanees
138!
139  ok_instan = .false.
140  call getin('OK_instan', ok_instan)
141!
142!Config  Key  = ecritphy
143!Config  Desc = Frequence d'ecriture dans histmth et histins
144!Config  Def  = 1
145!Config  Help = frequence de l'ecriture du fichier histmth et histins
146!Config         en jours.
147!
148       ecriphy = 1.
149       call getin('ecritphy', ecriphy)
150!
151!
152!Config Key  = if_ebil
153!Config Desc = Niveau de sortie pour les diags bilan d'energie
154!Config Def  = 0
155!Config Help =
156!               
157!
158  if_ebil = 0
159  call getin('if_ebil', if_ebil)
160!!
161!! Parametres orbitaux
162!!
163!Config Key  = R_ecc
164!Config Desc = Excentricite
165!Config Def  = 0.006787
166!Config Help =
167!               
168! VENUS
169! R_ecc = 0.006787
170  R_ecc   = 0.0
171  call getin('R_ecc', R_ecc)
172!!
173!Config Key  = R_peri
174!Config Desc = Equinoxe
175!Config Def  =
176!Config Help =
177!               
178! VENUS
179  R_peri = 0.
180  call getin('R_peri', R_peri)
181!!
182!Config Key  = R_incl
183!Config Desc = Inclinaison
184!Config Def  =
185!Config Help =
186!               
187! VENUS
188  R_incl = 0.0
189  call getin('R_incl', R_incl)
190!
191!
192!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
193! PARAMETER FOR THE PLANETARY BOUNDARY LAYER AND SOIL
194!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
195!
196!Config Key  = iflag_pbl
197!Config Desc =
198!Config Def  = 1
199!Config Help =
200!
201! 2   = calculs Cd et K simples pour VENUS :
202!       parametres = z0, lmixmin, ksta (en dur: umin2,ric,cepdu2,karman)
203! 1   = calculs Cd et K issus LMDZ Terre
204!       parametres = ksta, ok_kzmin (et plein d'autres en dur...)
205! 6-9 = schema des thermiques Fred
206  iflag_pbl = 1
207  call getin('iflag_pbl',iflag_pbl)
208
209!
210!Config Key  = ksta
211!Config Desc =
212!Config Def  = 1.0e-7
213!Config Help =
214!
215  ksta = 1.0e-7
216  call getin('ksta',ksta)
217
218!
219!Config Key  = z0
220!Config Desc =
221!Config Def  = 1.0e-2
222!Config Help =
223!
224  z0 = 1.0e-2
225  call getin('z0',z0)
226
227!
228!Config Key  = lmixmin
229!Config Desc =
230!Config Def  = 35.
231!Config Help =
232!
233  lmixmin = 35.
234  call getin('lmixmin',lmixmin)
235
236!
237!Config Key  = ok_kzmin
238!Config Desc =
239!Config Def  = .false.
240!Config Help =
241!
242  ok_kzmin = .false.
243  call getin('ok_kzmin',ok_kzmin)
244
245  ok_clmain = .true.
246  call getin('ok_clmain',ok_clmain)
247
248  physideal = .false.
249  call getin('physideal',physideal)
250
251!Config Key  = iflag_ajs
252!Config Desc =
253!Config Def  = 0
254!Config Help =
255!
256  iflag_ajs = 0
257  call getin('iflag_ajs',iflag_ajs)
258
259!
260!Config Key  = inertie
261!Config Desc =
262!Config Def  = 2000.
263!Config Help =
264!
265  inertie = 2000.
266  call getin('inertie',inertie)
267!
268!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
269! PARAMETER FOR THE OUTPUT LEVELS
270!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
271!
272!Config Key  = lev_histins
273!Config Desc =
274!Config Def  = 0
275!Config Help =
276!
277  lev_histins = 0
278  call getin('lev_histins',lev_histins)
279
280!
281!Config Key  = lev_histday
282!Config Desc =
283!Config Def  = 1
284!Config Help =
285!
286  lev_histday = 1
287  call getin('lev_histday',lev_histday)
288
289!
290!Config Key  = lev_histmth
291!Config Desc =
292!Config Def  = 2
293!Config Help =
294!
295  lev_histmth = 2
296  call getin('lev_histmth',lev_histmth)
297
298
299!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
300! PARAMETER FOR THE TRACERS
301!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
302!
303!Config Key  = tr_scheme
304!Config Desc =
305!Config Def  = 0
306!Config Help =
307!
308! 0   = Nothing is done (passive tracers)
309! 1   = pseudo-chemistry with relaxation toward fixed profile
310!       See Marcq&Lebonnois 2013
311! 2   = surface emission
312!       For the moment, inspired from Mars version
313!       However, the variable 'source' could be used in physiq
314!       so the call to phytrac_emiss could be to initialise it.
315! 3   = Full chemistry and/or clouds => phytrac_chimie
316!       Need ok_chem or ok_cloud
317  tr_scheme = 0
318  call getin('tr_scheme',tr_scheme)
319
320!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
321!   PARAMETRES DE LA CHIMIE/NUAGE dans physiq.def
322!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
323
324!
325!Config Key  = reinit_trac
326!Config Desc = 
327!Config Def  = .FALSE.
328!Config Help =
329!
330  reinit_trac = .FALSE.
331  call getin('reinit_trac',reinit_trac)
332 
333!
334!Config Key  = ok_cloud
335!Config Desc = 
336!Config Def  = .FALSE.
337!Config Help =
338!
339  ok_cloud = .false.
340  call getin('ok_cloud',ok_cloud)
341
342!
343!Config Key  = cl_scheme
344!Config Desc =
345!Config Def  = 2
346!Config Help =
347!
348! 1   = Simple microphysics (Aurelien Stolzenbach's PhD)
349! 2   = Full microphysics (momentum scheme, Sabrina Guilbon's PhD)
350
351  cl_scheme = 2
352  call getin('cl_scheme',cl_scheme)
353
354!
355!Config Key  = ok_chem
356!Config Desc = 
357!Config Def  = .FALSE.
358!Config Help =
359!
360  ok_chem = .false.
361  call getin('ok_chem',ok_chem)
362
363  if (((tr_scheme.ne.3).and.(ok_chem.or.ok_cloud)).or. &
364      ((tr_scheme.eq.3).and.(.not.ok_chem.and..not.ok_cloud))) then
365    write(*,*) "Attention, incoherence :"
366    write(*,*) "tr_scheme=",tr_scheme," / ok_chem=",ok_chem, &
367                                     " / ok_cloud=",ok_cloud
368    write(*,*) "Verifier votre physiq.def"
369    stop
370  endif
371
372!
373!Config Key  = ok_sedim
374!Config Desc = 
375!Config Def  = .FALSE.
376!Config Help =
377!
378  ok_sedim = .false.
379  call getin('ok_sedim',ok_sedim)
380
381!
382!Config Key  = nb_mode
383!Config Desc = 
384!Config Def  = 0
385!Config Help =
386!
387  nb_mode = 0
388  call getin('nb_mode',nb_mode)
389 
390!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
391! PARAMETER FOR SOLAR RADIATION
392!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
393
394!
395!Config Key  = solarchoice
396!Config Desc =
397!Config Def  = 1
398!Config Help =
399!
400! 1 = RH Tables
401! 2 = Generic module
402  solarchoice = 1
403  call getin('solarchoice',solarchoice)
404
405!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
406! PARAMETER FOR NLTE PHYSICS
407!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
408
409!
410!Config Key  = callnlte
411!Config Desc =
412!Config Def  = .false.
413!Config Help =
414!
415  callnlte = .false.
416  call getin('callnlte',callnlte)
417
418!
419!Config Key  = callnirco2
420!Config Desc =
421!Config Def  = .false.
422!
423  callnirco2 = .false.
424  call getin('callnirco2',callnirco2)
425
426!
427!Config Key  = nircorr
428!Config Desc =
429!Config Def  = 0
430!Config Help =
431!
432  nircorr = 0
433  call getin('nircorr',nircorr)
434
435!
436!Config Key  = callthermos
437!Config Desc =
438!Config Def  = .false.
439!Config Help =
440!
441  callthermos = .false.
442  call getin('callthermos',callthermos)
443
444!
445!Config Key  = nltemodel
446!Config Desc =
447!Config Def  = 0
448!Config Help =
449!
450  nltemodel = 0
451  call getin('nltemodel',nltemodel)
452
453!
454!Config Key  = solvarmod
455!Config Desc =
456!Config Def  = 1
457!Config Help =
458!
459  solvarmod = 1
460  call getin('solvarmod',solvarmod)
461
462!
463!Config Key  = fixed_euv_value
464!Config Desc =
465!Config Def  = 140.  ## Average solar cycle condition
466!Config Help =
467!
468  fixed_euv_value =140.
469  call getin('fixed_euv_value',fixed_euv_value)
470
471!
472!Config Key  = euveff
473!Config Desc =
474!Config Def  = 0.22
475!Config Help =
476!
477  euveff = 0.22
478  call getin('euveff',euveff)
479
480!Config Key  = tuneupperatm
481!Config Desc =
482!Config Def  = .false.
483!Config Help = Activate thermosphere tuning for oxygen compensation
484!
485  tuneupperatm = .false.
486  call getin('tuneupperatm',tuneupperatm)
487
488!
489!Config Key  = ok_jonline
490!Config Desc =
491!Config Def  = .false.
492!Config Help =
493!
494  ok_jonline = .false.
495  call getin('ok_jonline',ok_jonline)
496
497!
498!Config Key  = ok_ionchem
499!Config Desc =
500!Config Def  = .false.
501!Config Help = Activate the ionosphere chemistry
502!
503  ok_ionchem = .false.
504  call getin('ok_ionchem',ok_ionchem)
505
506  if ((ok_jonline.eqv..false.).and.(.true..eqv.ok_ionchem)) then
507    write(*,*) "Error incoherent flags :"
508    write(*,*) "ok_jonline=",ok_jonline," / ok_ionchem=",ok_ionchem
509    write(*,*) "If you include ions, ok_jonline==.true."
510    write(*,*) "If you do not include ions, ok_ionchem==.false."
511    write(*,*) "Check physiq.def"
512    stop
513  endif
514
515!
516!Config Key  = ok_iondiff
517!Config Desc =
518!Config Def  = .false.
519!Config Help = Activate the ambipolar ion diffusion in physic
520!
521  ok_iondiff = .false.
522  call getin('ok_iondiff',ok_iondiff)
523
524  if ((ok_ionchem.eqv..false.).and.(.true..eqv.ok_iondiff)) then
525    write(*,*) "Error incoherent flags :"
526    write(*,*) "ok_ionchem=",ok_ionchem," / ok_iondiff=",ok_iondiff
527    write(*,*) "If you include ions diffusion,"
528    write(*,*) "   you need also ok_ionchem==.true."
529    write(*,*) "If you do not include ions diffusion,"
530    write(*,*) "   you need ok_iondiff==.false."
531    write(*,*) "Check physiq.def"
532    stop
533  endif
534
535!
536!
537!Config Key  =
538!Config Desc = 
539!Config Def  =
540!Config Help =
541!
542!   =
543!  call getin('',)
544!
545!
546!
547!
548
549  write(lunout,*)' ##############################################'
550  write(lunout,*)' Configuration des parametres de la physique: '
551  write(lunout,*)' cycle_diurne = ', cycle_diurne
552  write(lunout,*)' soil_model = ', soil_model
553  write(lunout,*)' ok_orodr = ', ok_orodr
554  write(lunout,*)' ok_orolf = ', ok_orolf
555  write(lunout,*)' ok_gw_nonoro = ', ok_gw_nonoro
556  write(lunout,*)' nbapp_rad = ', nbapp_rad
557  write(lunout,*)' nbapp_chem = ', nbapp_chem
558  write(lunout,*)' iflag_con = ', iflag_con
559  write(lunout,*)' Sortie journaliere = ', ok_journe
560  write(lunout,*)' Sortie mensuelle = ', ok_mensuel
561  write(lunout,*)' Sortie instantanee = ', ok_instan
562  write(lunout,*)' frequence sorties = ', ecriphy 
563  write(lunout,*)' Sortie bilan d''energie, if_ebil =', if_ebil
564  write(lunout,*)' Excentricite = ',R_ecc
565  write(lunout,*)' Equinoxe = ',R_peri
566  write(lunout,*)' Inclinaison =',R_incl
567  write(lunout,*)' tr_scheme = ', tr_scheme
568  write(lunout,*)' iflag_pbl = ', iflag_pbl
569  write(lunout,*)' z0 = ',z0
570  write(lunout,*)' lmixmin = ',lmixmin
571  write(lunout,*)' ksta = ',ksta
572  write(lunout,*)' ok_kzmin = ',ok_kzmin
573  write(lunout,*)' inertie = ', inertie
574  write(lunout,*)' ok_clmain = ',ok_clmain
575  write(lunout,*)' physideal = ',physideal
576  write(lunout,*)' iflag_ajs = ', iflag_ajs
577  write(lunout,*)' lev_histins = ',lev_histins
578  write(lunout,*)' lev_histday = ',lev_histday
579  write(lunout,*)' lev_histmth = ',lev_histmth
580  write(lunout,*)' reinit_trac = ',reinit_trac
581  write(lunout,*)' ok_cloud = ',ok_cloud
582  write(lunout,*)' cl_scheme = ',cl_scheme
583  write(lunout,*)' ok_chem = ',ok_chem
584  write(lunout,*)' ok_sedim = ',ok_sedim
585  write(lunout,*)' nb_mode = ',nb_mode
586  write(lunout,*)' solarchoice = ',solarchoice
587  write(lunout,*)' callnlte = ',callnlte
588  write(lunout,*)' nltemodel = ',nltemodel
589  write(lunout,*)' callnirco2 = ',callnirco2
590  write(lunout,*)' nircorr = ',nircorr
591  write(lunout,*)' callthermos = ',callthermos
592  write(lunout,*)' solvarmod = ',solvarmod
593  write(lunout,*)' fixed_euv_value = ',fixed_euv_value
594  write(lunout,*)' euveff = ',euveff
595  write(lunout,*)' tuneupperatm = ',tuneupperatm
596  write(lunout,*)' ok_jonline = ',ok_jonline
597  write(lunout,*)' ok_ionchem = ',ok_ionchem
598  write(lunout,*)' ok_iondiff = ',ok_iondiff
599
600  end subroutine conf_phys
601
Note: See TracBrowser for help on using the repository browser.