source: trunk/LMDZ.MARS/libf/phymars/conf_phys.F @ 1467

Last change on this file since 1467 was 1467, checked in by tnavarro, 9 years ago

new option supersat to allow for supersaturation of water

File size: 27.9 KB
Line 
1      SUBROUTINE conf_phys(ngrid,nlayer,nq)
2 
3!=======================================================================
4!
5!   purpose:
6!   -------
7!
8!   Initialisation for the physical parametrisations of the LMD
9!   martian atmospheric general circulation modele.
10!
11!   author: Frederic Hourdin 15 / 10 /93
12!   -------
13!   modified: Sebastien Lebonnois 11/06/2003 (new callphys.def)
14!             Ehouarn Millour (oct. 2008) tracers are now identified
15!              by their names and may not be contiguously
16!              stored in the q(:,:,:,:) array
17!             E.M. (june 2009) use getin routine to load parameters
18!             adapted to the mesoscale use - Aymeric Spiga - 01/2007-07/2011
19!             separated inifis into conf_phys and phys_state_var_init (A. Spiga)
20!
21!
22!   arguments:
23!   ----------
24!
25!   input:
26!   ------
27!
28!    nq                    Number of tracers
29!
30!=======================================================================
31!
32!-----------------------------------------------------------------------
33!   declarations:
34!   -------------
35! to use  'getin'
36      USE ioipsl_getincom, only : getin
37      use tracer_mod, only : nuice_sed, ccn_factor
38      use surfdat_h, only: albedo_h2o_ice, inert_h2o_ice,
39     &                     frost_albedo_threshold
40      use control_mod, only: ecritphy
41      use planete_h
42      USE comcstfi_h, only: daysec,dtphys
43      use dimradmars_mod, only: naerkind, name_iaer,
44     &                      ini_scatterers,tauvis
45
46      IMPLICIT NONE
47#include "callkeys.h"
48#include "datafile.h"
49#include "microphys.h"
50
51      INTEGER,INTENT(IN) :: ngrid,nlayer,nq
52      INTEGER ig,ierr,j
53 
54      CHARACTER ch1*12
55      CHARACTER ch80*80
56
57      ! read in 'ecritphy' (frequency of calls to physics, in dynamical steps)
58      ! (also done in dyn3d/defrun_new but not in LMDZ.COMMON)
59      call getin("ecritphy",ecritphy)
60     
61! --------------------------------------------------------------
62!  Reading the "callphys.def" file controlling some key options
63! --------------------------------------------------------------
64     
65      ! check that 'callphys.def' file is around
66      OPEN(99,file='callphys.def',status='old',form='formatted'
67     &     ,iostat=ierr)
68      CLOSE(99)
69     
70      IF(ierr.EQ.0) THEN
71         PRINT*
72         PRINT*
73         PRINT*,'--------------------------------------------'
74         PRINT*,' conf_phys: Parameters for the physics (callphys.def)'
75         PRINT*,'--------------------------------------------'
76
77         write(*,*) "Directory where external input files are:"
78         datafile="/u/lmdz/WWW/planets/mars/datadir"
79         call getin("datadir",datafile) ! default path
80         write(*,*) " datafile = ",trim(datafile)
81
82         write(*,*) "Run with or without tracer transport ?"
83         tracer=.false. ! default value
84         call getin("tracer",tracer)
85         write(*,*) " tracer = ",tracer
86
87         write(*,*) "Diurnal cycle ?"
88         write(*,*) "(if diurnal=False, diurnal averaged solar heating)"
89         diurnal=.true. ! default value
90         call getin("diurnal",diurnal)
91         write(*,*) " diurnal = ",diurnal
92
93         write(*,*) "Seasonal cycle ?"
94         write(*,*) "(if season=False, Ls stays constant, to value ",
95     &   "set in 'start'"
96         season=.true. ! default value
97         call getin("season",season)
98         write(*,*) " season = ",season
99
100         write(*,*) "Write some extra output to the screen ?"
101         lwrite=.false. ! default value
102         call getin("lwrite",lwrite)
103         write(*,*) " lwrite = ",lwrite
104
105         write(*,*) "Save statistics in file stats.nc ?"
106#ifdef MESOSCALE
107         callstats=.false. ! default value
108#else
109         callstats=.true. ! default value
110#endif
111         call getin("callstats",callstats)
112         write(*,*) " callstats = ",callstats
113
114         write(*,*) "Save EOF profiles in file 'profiles' for ",
115     &              "Climate Database?"
116         calleofdump=.false. ! default value
117         call getin("calleofdump",calleofdump)
118         write(*,*) " calleofdump = ",calleofdump
119
120         write(*,*) "Dust scenario: 1=constant dust (read from startfi",
121     &   " or set as tauvis); 2=Viking scenario; =3 MGS scenario,",
122     &   "=6 cold (low dust) scenario; =7 warm (high dust) scenario ",
123     &   "=24,25 ... 30 :Mars Year 24, ... or 30 from TES assimilation"
124         iaervar=3 ! default value
125         call getin("iaervar",iaervar)
126         write(*,*) " iaervar = ",iaervar
127
128         write(*,*) "Reference (visible) dust opacity at 610 Pa ",
129     &   "(matters only if iaervar=1)"
130         ! NB: default value of tauvis is set/read in startfi.nc file
131         call getin("tauvis",tauvis)
132         write(*,*) " tauvis = ",tauvis
133
134         write(*,*) "Dust vertical distribution:"
135         write(*,*) "(=1 top set by topdustref parameter;",
136     & " =2 Viking scenario; =3 MGS scenario)"
137         iddist=3 ! default value
138         call getin("iddist",iddist)
139         write(*,*) " iddist = ",iddist
140
141         write(*,*) "Dust top altitude (km). (Matters only if iddist=1)"
142         topdustref= 90.0 ! default value
143         call getin("topdustref",topdustref)
144         write(*,*) " topdustref = ",topdustref
145
146         write(*,*) "Prescribed surface thermal flux (H/(rho*cp),K m/s)"
147         tke_heat_flux=0. ! default value
148         call getin("tke_heat_flux",tke_heat_flux)
149         write(*,*) " tke_heat_flux = ",tke_heat_flux
150         write(*,*) " 0 means the usual schemes are computing"
151
152         write(*,*) "call radiative transfer ?"
153         callrad=.true. ! default value
154         call getin("callrad",callrad)
155         write(*,*) " callrad = ",callrad
156
157         write(*,*) "call slope insolation scheme ?",
158     &              "(matters only if callrad=T)"
159#ifdef MESOSCALE
160         callslope=.true. ! default value
161#else
162         callslope=.false. ! default value (not supported yet)
163#endif
164         call getin("callslope",callslope)
165         write(*,*) " callslope = ",callslope
166
167         write(*,*) "call NLTE radiative schemes ?",
168     &              "(matters only if callrad=T)"
169         callnlte=.false. ! default value
170         call getin("callnlte",callnlte)
171         write(*,*) " callnlte = ",callnlte
172         
173         nltemodel=0    !default value
174         write(*,*) "NLTE model?"
175         write(*,*) "0 -> old model, static O"
176         write(*,*) "1 -> old model, dynamic O"
177         write(*,*) "2 -> new model"
178         write(*,*) "(matters only if callnlte=T)"
179         call getin("nltemodel",nltemodel)
180         write(*,*) " nltemodel = ",nltemodel
181
182         write(*,*) "call CO2 NIR absorption ?",
183     &              "(matters only if callrad=T)"
184         callnirco2=.false. ! default value
185         call getin("callnirco2",callnirco2)
186         write(*,*) " callnirco2 = ",callnirco2
187
188         write(*,*) "New NIR NLTE correction ?",
189     $              "0-> old model (no correction)",
190     $              "1-> new correction",
191     $              "(matters only if callnirco2=T)"
192#ifdef MESOSCALE
193         nircorr=0      !default value. this is OK below 60 km.
194#else
195         nircorr=0      !default value
196#endif
197         call getin("nircorr",nircorr)
198         write(*,*) " nircorr = ",nircorr
199
200         write(*,*) "call turbulent vertical diffusion ?"
201         calldifv=.true. ! default value
202         call getin("calldifv",calldifv)
203         write(*,*) " calldifv = ",calldifv
204
205         write(*,*) "call thermals ?"
206         calltherm=.false. ! default value
207         call getin("calltherm",calltherm)
208         write(*,*) " calltherm = ",calltherm
209
210         write(*,*) "call convective adjustment ?"
211         calladj=.true. ! default value
212         call getin("calladj",calladj)
213         write(*,*) " calladj = ",calladj
214
215         if (calltherm .and. calladj) then
216          print*,'!!! PLEASE NOTE !!!'
217          print*,'convective adjustment is on'
218          print*,'but since thermal plume model is on'
219          print*,'convadj is only activated above the PBL'
220         endif
221       
222         write(*,*) "used latest version of yamada scheme?"
223         callyamada4=.true. ! default value
224         call getin("callyamada4",callyamada4)
225         write(*,*) " callyamada4 = ",callyamada4
226
227         if (calltherm .and. .not.callyamada4) then
228          print*,'!!!! WARNING WARNING WARNING !!!!'
229          print*,'if calltherm=T we strongly advise that '
230          print*,'you set the flag callyamada4 to T '
231          print*,'!!!! WARNING WARNING WARNING !!!!'
232         endif
233 
234         write(*,*) "call Richardson-based surface layer ?"
235         callrichsl=.false. ! default value
236         call getin("callrichsl",callrichsl)
237         write(*,*) " callrichsl = ",callrichsl
238
239         if (calltherm .and. .not.callrichsl) then
240          print*,'WARNING WARNING WARNING'
241          print*,'if calltherm=T we strongly advise that '
242          print*,'you use the new surface layer scheme '
243          print*,'by setting callrichsl=T '
244         endif
245
246         if (calladj .and. callrichsl .and. (.not. calltherm)) then
247          print*,'You should not be calling the convective adjustment
248     & scheme with the Richardson surface-layer and without the thermals
249     &. This approach is not
250     & physically consistent and can lead to unrealistic friction
251     & values.'
252          print*,'If you want to use the Ri. surface-layer, either
253     & activate thermals OR de-activate the convective adjustment.'
254          stop
255         endif
256
257         write(*,*) "call CO2 condensation ?"
258         callcond=.true. ! default value
259         call getin("callcond",callcond)
260         write(*,*) " callcond = ",callcond
261
262         write(*,*)"call thermal conduction in the soil ?"
263         callsoil=.true. ! default value
264         call getin("callsoil",callsoil)
265         write(*,*) " callsoil = ",callsoil
266         
267
268         write(*,*)"call Lott's gravity wave/subgrid topography ",
269     &             "scheme ?"
270         calllott=.true. ! default value
271         call getin("calllott",calllott)
272         write(*,*)" calllott = ",calllott
273
274
275         write(*,*)"rad.transfer is computed every iradia",
276     &             " physical timestep"
277         iradia=1 ! default value
278         call getin("iradia",iradia)
279         write(*,*)" iradia = ",iradia
280         
281
282         write(*,*)"Output of the exchange coefficient mattrix ?",
283     &             "(for diagnostics only)"
284         callg2d=.false. ! default value
285         call getin("callg2d",callg2d)
286         write(*,*)" callg2d = ",callg2d
287
288         write(*,*)"Rayleigh scattering : (should be .false. for now)"
289         rayleigh=.false.
290         call getin("rayleigh",rayleigh)
291         write(*,*)" rayleigh = ",rayleigh
292
293
294! TRACERS:
295
296! dustbin
297         write(*,*)"Transported dust ? (if >0, use 'dustbin' dust bins)"
298         dustbin=0 ! default value
299         call getin("dustbin",dustbin)
300         write(*,*)" dustbin = ",dustbin
301! active
302         write(*,*)"Radiatively active dust ? (matters if dustbin>0)"
303         active=.false. ! default value
304         call getin("active",active)
305         write(*,*)" active = ",active
306
307! Test of incompatibility:
308! if active is used, then dustbin should be > 0
309
310         if (active.and.(dustbin.lt.1)) then
311           print*,'if active is used, then dustbin should > 0'
312           stop
313         endif
314! doubleq
315         write(*,*)"use mass and number mixing ratios to predict",
316     &             " dust size ?"
317         doubleq=.false. ! default value
318         call getin("doubleq",doubleq)
319         write(*,*)" doubleq = ",doubleq
320! submicron
321         submicron=.false. ! default value
322         call getin("submicron",submicron)
323         write(*,*)" submicron = ",submicron
324
325! Test of incompatibility:
326! if doubleq is used, then dustbin should be 2
327
328         if (doubleq.and.(dustbin.ne.2)) then
329           print*,'if doubleq is used, then dustbin should be 2'
330           stop
331         endif
332         if (doubleq.and.submicron.and.(nq.LT.3)) then
333           print*,'If doubleq is used with a submicron tracer,'
334           print*,' then the number of tracers has to be'
335           print*,' larger than 3.'
336           stop
337         endif
338
339! lifting
340         write(*,*)"dust lifted by GCM surface winds ?"
341         lifting=.false. ! default value
342         call getin("lifting",lifting)
343         write(*,*)" lifting = ",lifting
344
345! Test of incompatibility:
346! if lifting is used, then dustbin should be > 0
347
348         if (lifting.and.(dustbin.lt.1)) then
349           print*,'if lifting is used, then dustbin should > 0'
350           stop
351         endif
352
353! free evolving dust
354! freedust=true just says that there is no lifting and no dust opacity scaling.
355         write(*,*)"dust lifted by GCM surface winds ?"
356         freedust=.false. ! default value
357         call getin("freedust",freedust)
358         write(*,*)" freedust = ",freedust
359         if (freedust.and..not.doubleq) then
360           print*,'freedust should be used with doubleq !'
361           stop
362         endif
363#ifndef MESOSCALE
364         ! this test is valid in GCM case
365         ! ... not in mesoscale case, for we want to activate mesoscale lifting
366         if (freedust.and.lifting) then
367           print*,'if freedust is used, then lifting should not be used'
368           print*,'lifting forced to false !!'
369           lifting=.false.
370         endif
371#endif
372
373! Dust IR opacity
374         write(*,*)" Wavelength for infrared opacity of dust ?"
375         write(*,*)" Choices are:"
376         write(*,*)" tes  --- > 9.3 microns  [default]"
377         write(*,*)" mcs  --- > 21.6 microns"
378         !
379         ! WARNING WARNING WARNING WARNING WARNING WARNING
380         !
381         ! BEFORE ADDING A NEW VALUE, BE SURE THAT THE
382         ! CORRESPONDING WAVELENGTH IS IN THE LOOKUP TABLE,
383         ! OR AT LEAST NO TO FAR, TO AVOID FALLACIOUS INTERPOLATIONS.
384         !
385         dustiropacity="tes" !default value - is expected to shift to mcs one day
386         call getin("dustiropacity",dustiropacity)
387         write(*,*)" dustiropacity = ",trim(dustiropacity)
388         select case (trim(dustiropacity))
389           case ("tes")
390             dustrefir = 9.3E-6
391           case ("mcs")
392             dustrefir = 21.6E-6
393           case default
394              write(*,*) trim(dustiropacity),
395     &                  " is not a valid option for dustiropacity"
396             stop
397         end select
398
399! callddevil
400         write(*,*)" dust lifted by dust devils ?"
401         callddevil=.false. !default value
402         call getin("callddevil",callddevil)
403         write(*,*)" callddevil = ",callddevil
404
405! Test of incompatibility:
406! if dustdevil is used, then dustbin should be > 0
407
408         if (callddevil.and.(dustbin.lt.1)) then
409           print*,'if dustdevil is used, then dustbin should > 0'
410           stop
411         endif
412! sedimentation
413         write(*,*) "Gravitationnal sedimentation ?"
414         sedimentation=.true. ! default value
415         call getin("sedimentation",sedimentation)
416         write(*,*) " sedimentation = ",sedimentation
417! activice
418         write(*,*) "Radiatively active transported atmospheric ",
419     &              "water ice ?"
420         activice=.false. ! default value
421         call getin("activice",activice)
422         write(*,*) " activice = ",activice
423! water
424         write(*,*) "Compute water cycle ?"
425         water=.false. ! default value
426         call getin("water",water)
427         write(*,*) " water = ",water
428
429! thermal inertia feedback
430         write(*,*) "Activate the thermal inertia feedback ?"
431         tifeedback=.false. ! default value
432         call getin("tifeedback",tifeedback)
433         write(*,*) " tifeedback = ",tifeedback
434
435! Test of incompatibility:
436
437         if (tifeedback.and..not.water) then
438           print*,'if tifeedback is used,'
439           print*,'water should be used too'
440           stop
441         endif
442
443         if (tifeedback.and..not.callsoil) then
444           print*,'if tifeedback is used,'
445           print*,'callsoil should be used too'
446           stop
447         endif
448
449         if (activice.and..not.water) then
450           print*,'if activice is used, water should be used too'
451           stop
452         endif
453
454         if (water.and..not.tracer) then
455           print*,'if water is used, tracer should be used too'
456           stop
457         endif
458         
459! water ice clouds effective variance distribution for sedimentaion       
460        write(*,*) "effective variance for water ice clouds ?"
461        nuice_sed=0.45
462        call getin("nuice_sed",nuice_sed)
463        write(*,*) "water_param nueff Sedimentation:", nuice_sed
464         
465! ccn factor if no scavenging         
466        write(*,*) "water param CCN reduc. factor ?", ccn_factor
467        ccn_factor = 4.5
468        call getin("ccn_factor",ccn_factor)
469        write(*,*)" ccn_factor = ",ccn_factor
470        write(*,*)"Careful: only used when microphys=F, otherwise"
471        write(*,*)"the contact parameter is used instead;"
472
473! microphys
474         write(*,*)"Microphysical scheme for water-ice clouds?"
475         microphys=.false. ! default value
476         call getin("microphys",microphys)
477         write(*,*)" microphys = ",microphys
478
479! supersat
480         write(*,*)"Allow super-saturation of water vapor?"
481         supersat=.true. ! default value
482         call getin("supersat",supersat)
483         write(*,*)"supersat = ",supersat
484
485! microphysical parameter contact       
486         write(*,*) "water contact parameter ?"
487         mteta  = 0.95
488         call getin("mteta",mteta)
489         write(*,*) "mteta = ", mteta
490
491! scavenging
492         write(*,*)"Dust scavenging by H2O/CO2 snowfall ?"
493         scavenging=.false. ! default value
494         call getin("scavenging",scavenging)
495         write(*,*)" scavenging = ",scavenging
496         
497
498! Test of incompatibility:
499! if scavenging is used, then dustbin should be > 0
500
501         if ((microphys.and..not.doubleq).or.
502     &       (microphys.and..not.water)) then
503             print*,'if microphys is used, then doubleq,'
504             print*,'and water must be used!'
505             stop
506         endif
507         if (microphys.and..not.scavenging) then
508             print*,''
509             print*,'----------------WARNING-----------------'
510             print*,'microphys is used without scavenging !!!'
511             print*,'----------------WARNING-----------------'
512             print*,''
513         endif
514
515         if ((scavenging.and..not.microphys).or.
516     &       (scavenging.and.(dustbin.lt.1))) then
517             print*,'if scavenging is used, then microphys'
518             print*,'must be used!'
519             stop
520         endif
521
522! Test of incompatibility:
523
524         write(*,*) "Permanent water caps at poles ?",
525     &               " .true. is RECOMMENDED"
526         write(*,*) "(with .true., North cap is a source of water ",
527     &   "and South pole is a cold trap)"
528         caps=.true. ! default value
529         call getin("caps",caps)
530         write(*,*) " caps = ",caps
531
532! albedo_h2o_ice
533         write(*,*) "water ice albedo ?"
534         albedo_h2o_ice=0.45
535         call getin("albedo_h2o_ice",albedo_h2o_ice)
536         write(*,*) " albedo_h2o_ice = ",albedo_h2o_ice
537! inert_h2o_ice
538         write(*,*) "water ice thermal inertia ?"
539         inert_h2o_ice=2400 ! (J.m^-2.K^-1.s^-1/2)
540         call getin("inert_h2o_ice",inert_h2o_ice)
541         write(*,*) " inert_h2o_ice = ",inert_h2o_ice
542! frost_albedo_threshold
543         write(*,*) "frost thickness threshold for albedo ?"
544         frost_albedo_threshold=0.005 ! 5.4 mic (i.e 0.005 kg.m-2)
545         call getin("frost_albedo_threshold",
546     &    frost_albedo_threshold)
547         write(*,*) " frost_albedo_threshold = ",
548     &            frost_albedo_threshold
549
550! call Titus crocus line -- DEFAULT IS NONE
551         write(*,*) "Titus crocus line ?"
552         tituscap=.false.  ! default value
553         call getin("tituscap",tituscap)
554         write(*,*) "tituscap",tituscap
555                     
556
557         write(*,*) "photochemistry: include chemical species"
558         photochem=.false. ! default value
559         call getin("photochem",photochem)
560         write(*,*) " photochem = ",photochem
561
562
563! SCATTERERS
564         write(*,*) "how many scatterers?"
565         naerkind=1 ! default value
566         call getin("naerkind",naerkind)
567         write(*,*)" naerkind = ",naerkind
568
569! Test of incompatibility
570c        Logical tests for radiatively active water-ice clouds:
571         IF ( (activice.AND.(.NOT.water)).OR.
572     &        (activice.AND.(naerkind.LT.2)) ) THEN
573           WRITE(*,*) 'If activice is TRUE, water has to be set'
574           WRITE(*,*) 'to TRUE, and "naerkind" must be at least'
575           WRITE(*,*) 'equal to 2.'
576           CALL ABORT
577         ELSE IF ( (.NOT.activice).AND.(naerkind.GT.1) ) THEN
578           WRITE(*,*) 'naerkind is greater than unity, but'
579           WRITE(*,*) 'activice has not been set to .true.'
580           WRITE(*,*) 'in callphys.def; this is not logical!'
581           CALL ABORT
582         ENDIF
583
584!------------------------------------------
585!------------------------------------------
586! once naerkind is known allocate arrays
587! -- we do it here and not in phys_var_init
588! -- because we need to know naerkind first
589         CALL ini_scatterers(ngrid,nlayer)
590!------------------------------------------
591!------------------------------------------
592
593
594c        Please name the different scatterers here ----------------
595         name_iaer(1) = "dust_conrath"   !! default choice is good old Conrath profile
596         IF (doubleq.AND.active) name_iaer(1) = "dust_doubleq" !! two-moment scheme
597         if (nq.gt.1) then
598          ! trick to avoid problems compiling with 1 tracer
599          ! and picky compilers who know name_iaer(2) is out of bounds
600          j=2
601         IF (water.AND.activice) name_iaer(j) = "h2o_ice"      !! radiatively-active clouds
602         IF (submicron.AND.active) name_iaer(j) = "dust_submicron" !! JBM experimental stuff
603         endif ! of if (nq.gt.1)
604c        ----------------------------------------------------------
605
606! THERMOSPHERE
607
608         write(*,*) "call thermosphere ?"
609         callthermos=.false. ! default value
610         call getin("callthermos",callthermos)
611         write(*,*) " callthermos = ",callthermos
612         
613
614         write(*,*) " water included without cycle ",
615     &              "(only if water=.false.)"
616         thermoswater=.false. ! default value
617         call getin("thermoswater",thermoswater)
618         write(*,*) " thermoswater = ",thermoswater
619
620         write(*,*) "call thermal conduction ?",
621     &    " (only if callthermos=.true.)"
622         callconduct=.false. ! default value
623         call getin("callconduct",callconduct)
624         write(*,*) " callconduct = ",callconduct
625
626         write(*,*) "call EUV heating ?",
627     &   " (only if callthermos=.true.)"
628         calleuv=.false.  ! default value
629         call getin("calleuv",calleuv)
630         write(*,*) " calleuv = ",calleuv
631
632         write(*,*) "call molecular viscosity ?",
633     &   " (only if callthermos=.true.)"
634         callmolvis=.false. ! default value
635         call getin("callmolvis",callmolvis)
636         write(*,*) " callmolvis = ",callmolvis
637
638         write(*,*) "call molecular diffusion ?",
639     &   " (only if callthermos=.true.)"
640         callmoldiff=.false. ! default value
641         call getin("callmoldiff",callmoldiff)
642         write(*,*) " callmoldiff = ",callmoldiff
643         
644
645         write(*,*) "call thermospheric photochemistry ?",
646     &   " (only if callthermos=.true.)"
647         thermochem=.false. ! default value
648         call getin("thermochem",thermochem)
649         write(*,*) " thermochem = ",thermochem
650
651         write(*,*) "Method to include solar variability"
652         write(*,*) "0-> old method (using solarcondate); ",
653     &                  "1-> variability wit E10.7"
654         solvarmod=1
655         call getin("solvarmod",solvarmod)
656         write(*,*) " solvarmod = ",solvarmod
657
658         write(*,*) "date for solar flux calculation:",
659     &   " (1985 < date < 2002)",
660     $   " (Only used if solvarmod=0)"
661         write(*,*) "(Solar min=1996.4 ave=1993.4 max=1990.6)"
662         solarcondate=1993.4 ! default value
663         call getin("solarcondate",solarcondate)
664         write(*,*) " solarcondate = ",solarcondate
665         
666         write(*,*) "Solar variability as observed for MY: "
667         write(*,*) "Only if solvarmod=1"
668         solvaryear=24
669         call getin("solvaryear",solvaryear)
670         write(*,*) " solvaryear = ",solvaryear
671
672         write(*,*) "UV heating efficiency:",
673     &   "measured values between 0.19 and 0.23 (Fox et al. 1996)",
674     &   "lower values may be used to compensate low 15 um cooling"
675         euveff=0.21 !default value
676         call getin("euveff",euveff)
677         write(*,*) " euveff = ", euveff
678
679         if (.not.callthermos) then
680           if (thermoswater) then
681             print*,'if thermoswater is set, callthermos must be true'
682             stop
683           endif         
684           if (callconduct) then
685             print*,'if callconduct is set, callthermos must be true'
686             stop
687           endif       
688           if (calleuv) then
689             print*,'if calleuv is set, callthermos must be true'
690             stop
691           endif         
692           if (callmolvis) then
693             print*,'if callmolvis is set, callthermos must be true'
694             stop
695           endif       
696           if (callmoldiff) then
697             print*,'if callmoldiff is set, callthermos must be true'
698             stop
699           endif         
700           if (thermochem) then
701             print*,'if thermochem is set, callthermos must be true'
702             stop
703           endif         
704        endif
705
706! Test of incompatibility:
707! if photochem is used, then water should be used too
708
709         if (photochem.and..not.water) then
710           print*,'if photochem is used, water should be used too'
711           stop
712         endif
713
714! if callthermos is used, then thermoswater should be used too
715! (if water not used already)
716
717         if (callthermos .and. .not.water) then
718           if (callthermos .and. .not.thermoswater) then
719             print*,'if callthermos is used, water or thermoswater
720     &               should be used too'
721             stop
722           endif
723         endif
724
725         PRINT*,'--------------------------------------------'
726         PRINT*
727         PRINT*
728      ELSE
729         write(*,*)
730         write(*,*) 'Cannot read file callphys.def. Is it here ?'
731         stop
732      ENDIF
733
7348000  FORMAT(t5,a12,l8)
7358001  FORMAT(t5,a12,i8)
736
737      PRINT*
738      PRINT*,'conf_phys: daysec',daysec
739      PRINT*
740      PRINT*,'conf_phys: The radiative transfer is computed:'
741      PRINT*,'           each ',iradia,' physical time-step'
742      PRINT*,'        or each ',iradia*dtphys,' seconds'
743      PRINT*
744! --------------------------------------------------------------
745!  Managing the Longwave radiative transfer
746! --------------------------------------------------------------
747
748!     In most cases, the run just use the following values :
749!     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
750      callemis=.true.     
751!     ilwd=10*int(daysec/dtphys) ! bug before 22/10/01       
752      ilwd=1
753      ilwn=1 !2
754      ilwb=1 !2
755      linear=.true.       
756      ncouche=3
757      alphan=0.4
758      semi=0
759
760!     BUT people working hard on the LW may want to read them in 'radia.def'
761!     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
762
763      OPEN(99,file='radia.def',status='old',form='formatted'
764     .     ,iostat=ierr)
765      IF(ierr.EQ.0) THEN
766         write(*,*) 'conf_phys: Reading radia.def !!!'
767         READ(99,fmt='(a)') ch1
768         READ(99,*) callemis
769         WRITE(*,8000) ch1,callemis
770
771         READ(99,fmt='(a)') ch1
772         READ(99,*) iradia
773         WRITE(*,8001) ch1,iradia
774
775         READ(99,fmt='(a)') ch1
776         READ(99,*) ilwd
777         WRITE(*,8001) ch1,ilwd
778
779         READ(99,fmt='(a)') ch1
780         READ(99,*) ilwn
781         WRITE(*,8001) ch1,ilwn
782
783         READ(99,fmt='(a)') ch1
784         READ(99,*) linear
785         WRITE(*,8000) ch1,linear
786
787         READ(99,fmt='(a)') ch1
788         READ(99,*) ncouche
789         WRITE(*,8001) ch1,ncouche
790
791         READ(99,fmt='(a)') ch1
792         READ(99,*) alphan
793         WRITE(*,*) ch1,alphan
794
795         READ(99,fmt='(a)') ch1
796         READ(99,*) ilwb
797         WRITE(*,8001) ch1,ilwb
798
799
800         READ(99,fmt='(a)') ch1
801         READ(99,'(l1)') callg2d
802         WRITE(*,8000) ch1,callg2d
803
804         READ(99,fmt='(a)') ch1
805         READ(99,*) semi
806         WRITE(*,*) ch1,semi
807      end if
808      CLOSE(99)
809
810      END
Note: See TracBrowser for help on using the repository browser.