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

Last change on this file since 1268 was 1268, checked in by aslmd, 11 years ago

LMDZ.MARS. related to r1266. forgot to remove a few now-obsolete dimensions.h includes in Mars physics.

File size: 26.7 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/forget/WWW/datagcm/datafile"
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! callddevil
374         write(*,*)" dust lifted by dust devils ?"
375         callddevil=.false. !default value
376         call getin("callddevil",callddevil)
377         write(*,*)" callddevil = ",callddevil
378
379! Test of incompatibility:
380! if dustdevil is used, then dustbin should be > 0
381
382         if (callddevil.and.(dustbin.lt.1)) then
383           print*,'if dustdevil is used, then dustbin should > 0'
384           stop
385         endif
386! sedimentation
387         write(*,*) "Gravitationnal sedimentation ?"
388         sedimentation=.true. ! default value
389         call getin("sedimentation",sedimentation)
390         write(*,*) " sedimentation = ",sedimentation
391! activice
392         write(*,*) "Radiatively active transported atmospheric ",
393     &              "water ice ?"
394         activice=.false. ! default value
395         call getin("activice",activice)
396         write(*,*) " activice = ",activice
397! water
398         write(*,*) "Compute water cycle ?"
399         water=.false. ! default value
400         call getin("water",water)
401         write(*,*) " water = ",water
402
403! thermal inertia feedback
404         write(*,*) "Activate the thermal inertia feedback ?"
405         tifeedback=.false. ! default value
406         call getin("tifeedback",tifeedback)
407         write(*,*) " tifeedback = ",tifeedback
408
409! Test of incompatibility:
410
411         if (tifeedback.and..not.water) then
412           print*,'if tifeedback is used,'
413           print*,'water should be used too'
414           stop
415         endif
416
417         if (tifeedback.and..not.callsoil) then
418           print*,'if tifeedback is used,'
419           print*,'callsoil should be used too'
420           stop
421         endif
422
423         if (activice.and..not.water) then
424           print*,'if activice is used, water should be used too'
425           stop
426         endif
427
428         if (water.and..not.tracer) then
429           print*,'if water is used, tracer should be used too'
430           stop
431         endif
432         
433! water ice clouds effective variance distribution for sedimentaion       
434        write(*,*) "effective variance for water ice clouds ?"
435        nuice_sed=0.45
436        call getin("nuice_sed",nuice_sed)
437        write(*,*) "water_param nueff Sedimentation:", nuice_sed
438         
439! ccn factor if no scavenging         
440        write(*,*) "water param CCN reduc. factor ?", ccn_factor
441        ccn_factor = 4.5
442        call getin("ccn_factor",ccn_factor)
443        write(*,*)" ccn_factor = ",ccn_factor
444        write(*,*)"Careful: only used when microphys=F, otherwise"
445        write(*,*)"the contact parameter is used instead;"
446
447! microphys
448         write(*,*)"Microphysical scheme for water-ice clouds?"
449         microphys=.false. ! default value
450         call getin("microphys",microphys)
451         write(*,*)" microphys = ",microphys
452
453! microphysical parameter contact       
454         write(*,*) "water contact parameter ?"
455         mteta  = 0.95
456         call getin("mteta",mteta)
457         write(*,*) "mteta = ", mteta
458
459! scavenging
460         write(*,*)"Dust scavenging by H2O/CO2 snowfall ?"
461         scavenging=.false. ! default value
462         call getin("scavenging",scavenging)
463         write(*,*)" scavenging = ",scavenging
464         
465
466! Test of incompatibility:
467! if scavenging is used, then dustbin should be > 0
468
469         if ((microphys.and..not.doubleq).or.
470     &       (microphys.and..not.water)) then
471             print*,'if microphys is used, then doubleq,'
472             print*,'and water must be used!'
473             stop
474         endif
475         if (microphys.and..not.scavenging) then
476             print*,''
477             print*,'----------------WARNING-----------------'
478             print*,'microphys is used without scavenging !!!'
479             print*,'----------------WARNING-----------------'
480             print*,''
481         endif
482
483         if ((scavenging.and..not.microphys).or.
484     &       (scavenging.and.(dustbin.lt.1))) then
485             print*,'if scavenging is used, then microphys'
486             print*,'must be used!'
487             stop
488         endif
489
490! Test of incompatibility:
491
492         write(*,*) "Permanent water caps at poles ?",
493     &               " .true. is RECOMMENDED"
494         write(*,*) "(with .true., North cap is a source of water ",
495     &   "and South pole is a cold trap)"
496         caps=.true. ! default value
497         call getin("caps",caps)
498         write(*,*) " caps = ",caps
499
500! albedo_h2o_ice
501         write(*,*) "water ice albedo ?"
502         albedo_h2o_ice=0.45
503         call getin("albedo_h2o_ice",albedo_h2o_ice)
504         write(*,*) " albedo_h2o_ice = ",albedo_h2o_ice
505! inert_h2o_ice
506         write(*,*) "water ice thermal inertia ?"
507         inert_h2o_ice=2400 ! (J.m^-2.K^-1.s^-1/2)
508         call getin("inert_h2o_ice",inert_h2o_ice)
509         write(*,*) " inert_h2o_ice = ",inert_h2o_ice
510! frost_albedo_threshold
511         write(*,*) "frost thickness threshold for albedo ?"
512         frost_albedo_threshold=0.005 ! 5.4 mic (i.e 0.005 kg.m-2)
513         call getin("frost_albedo_threshold",
514     &    frost_albedo_threshold)
515         write(*,*) " frost_albedo_threshold = ",
516     &            frost_albedo_threshold
517
518! call Titus crocus line -- DEFAULT IS NONE
519         write(*,*) "Titus crocus line ?"
520         tituscap=.false.  ! default value
521         call getin("tituscap",tituscap)
522         write(*,*) "tituscap",tituscap
523                     
524
525         write(*,*) "photochemistry: include chemical species"
526         photochem=.false. ! default value
527         call getin("photochem",photochem)
528         write(*,*) " photochem = ",photochem
529
530
531! SCATTERERS
532         write(*,*) "how many scatterers?"
533         naerkind=1 ! default value
534         call getin("naerkind",naerkind)
535         write(*,*)" naerkind = ",naerkind
536
537! Test of incompatibility
538c        Logical tests for radiatively active water-ice clouds:
539         IF ( (activice.AND.(.NOT.water)).OR.
540     &        (activice.AND.(naerkind.LT.2)) ) THEN
541           WRITE(*,*) 'If activice is TRUE, water has to be set'
542           WRITE(*,*) 'to TRUE, and "naerkind" must be at least'
543           WRITE(*,*) 'equal to 2.'
544           CALL ABORT
545         ELSE IF ( (.NOT.activice).AND.(naerkind.GT.1) ) THEN
546           WRITE(*,*) 'naerkind is greater than unity, but'
547           WRITE(*,*) 'activice has not been set to .true.'
548           WRITE(*,*) 'in callphys.def; this is not logical!'
549           CALL ABORT
550         ENDIF
551
552!------------------------------------------
553!------------------------------------------
554! once naerkind is known allocate arrays
555! -- we do it here and not in phys_var_init
556! -- because we need to know naerkind first
557         CALL ini_scatterers(ngrid,nlayer)
558!------------------------------------------
559!------------------------------------------
560
561
562c        Please name the different scatterers here ----------------
563         name_iaer(1) = "dust_conrath"   !! default choice is good old Conrath profile
564         IF (doubleq.AND.active) name_iaer(1) = "dust_doubleq" !! two-moment scheme
565         if (nq.gt.1) then
566          ! trick to avoid problems compiling with 1 tracer
567          ! and picky compilers who know name_iaer(2) is out of bounds
568          j=2
569         IF (water.AND.activice) name_iaer(j) = "h2o_ice"      !! radiatively-active clouds
570         IF (submicron.AND.active) name_iaer(j) = "dust_submicron" !! JBM experimental stuff
571         endif ! of if (nq.gt.1)
572c        ----------------------------------------------------------
573
574! THERMOSPHERE
575
576         write(*,*) "call thermosphere ?"
577         callthermos=.false. ! default value
578         call getin("callthermos",callthermos)
579         write(*,*) " callthermos = ",callthermos
580         
581
582         write(*,*) " water included without cycle ",
583     &              "(only if water=.false.)"
584         thermoswater=.false. ! default value
585         call getin("thermoswater",thermoswater)
586         write(*,*) " thermoswater = ",thermoswater
587
588         write(*,*) "call thermal conduction ?",
589     &    " (only if callthermos=.true.)"
590         callconduct=.false. ! default value
591         call getin("callconduct",callconduct)
592         write(*,*) " callconduct = ",callconduct
593
594         write(*,*) "call EUV heating ?",
595     &   " (only if callthermos=.true.)"
596         calleuv=.false.  ! default value
597         call getin("calleuv",calleuv)
598         write(*,*) " calleuv = ",calleuv
599
600         write(*,*) "call molecular viscosity ?",
601     &   " (only if callthermos=.true.)"
602         callmolvis=.false. ! default value
603         call getin("callmolvis",callmolvis)
604         write(*,*) " callmolvis = ",callmolvis
605
606         write(*,*) "call molecular diffusion ?",
607     &   " (only if callthermos=.true.)"
608         callmoldiff=.false. ! default value
609         call getin("callmoldiff",callmoldiff)
610         write(*,*) " callmoldiff = ",callmoldiff
611         
612
613         write(*,*) "call thermospheric photochemistry ?",
614     &   " (only if callthermos=.true.)"
615         thermochem=.false. ! default value
616         call getin("thermochem",thermochem)
617         write(*,*) " thermochem = ",thermochem
618
619         write(*,*) "Method to include solar variability"
620         write(*,*) "0-> old method (using solarcondate); ",
621     &                  "1-> variability wit E10.7"
622         solvarmod=1
623         call getin("solvarmod",solvarmod)
624         write(*,*) " solvarmod = ",solvarmod
625
626         write(*,*) "date for solar flux calculation:",
627     &   " (1985 < date < 2002)",
628     $   " (Only used if solvarmod=0)"
629         write(*,*) "(Solar min=1996.4 ave=1993.4 max=1990.6)"
630         solarcondate=1993.4 ! default value
631         call getin("solarcondate",solarcondate)
632         write(*,*) " solarcondate = ",solarcondate
633         
634         write(*,*) "Solar variability as observed for MY: "
635         write(*,*) "Only if solvarmod=1"
636         solvaryear=24
637         call getin("solvaryear",solvaryear)
638         write(*,*) " solvaryear = ",solvaryear
639
640         write(*,*) "UV heating efficiency:",
641     &   "measured values between 0.19 and 0.23 (Fox et al. 1996)",
642     &   "lower values may be used to compensate low 15 um cooling"
643         euveff=0.21 !default value
644         call getin("euveff",euveff)
645         write(*,*) " euveff = ", euveff
646
647         if (.not.callthermos) then
648           if (thermoswater) then
649             print*,'if thermoswater is set, callthermos must be true'
650             stop
651           endif         
652           if (callconduct) then
653             print*,'if callconduct is set, callthermos must be true'
654             stop
655           endif       
656           if (calleuv) then
657             print*,'if calleuv is set, callthermos must be true'
658             stop
659           endif         
660           if (callmolvis) then
661             print*,'if callmolvis is set, callthermos must be true'
662             stop
663           endif       
664           if (callmoldiff) then
665             print*,'if callmoldiff is set, callthermos must be true'
666             stop
667           endif         
668           if (thermochem) then
669             print*,'if thermochem is set, callthermos must be true'
670             stop
671           endif         
672        endif
673
674! Test of incompatibility:
675! if photochem is used, then water should be used too
676
677         if (photochem.and..not.water) then
678           print*,'if photochem is used, water should be used too'
679           stop
680         endif
681
682! if callthermos is used, then thermoswater should be used too
683! (if water not used already)
684
685         if (callthermos .and. .not.water) then
686           if (callthermos .and. .not.thermoswater) then
687             print*,'if callthermos is used, water or thermoswater
688     &               should be used too'
689             stop
690           endif
691         endif
692
693         PRINT*,'--------------------------------------------'
694         PRINT*
695         PRINT*
696      ELSE
697         write(*,*)
698         write(*,*) 'Cannot read file callphys.def. Is it here ?'
699         stop
700      ENDIF
701
7028000  FORMAT(t5,a12,l8)
7038001  FORMAT(t5,a12,i8)
704
705      PRINT*
706      PRINT*,'conf_phys: daysec',daysec
707      PRINT*
708      PRINT*,'conf_phys: The radiative transfer is computed:'
709      PRINT*,'           each ',iradia,' physical time-step'
710      PRINT*,'        or each ',iradia*dtphys,' seconds'
711      PRINT*
712! --------------------------------------------------------------
713!  Managing the Longwave radiative transfer
714! --------------------------------------------------------------
715
716!     In most cases, the run just use the following values :
717!     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
718      callemis=.true.     
719!     ilwd=10*int(daysec/dtphys) ! bug before 22/10/01       
720      ilwd=1
721      ilwn=1 !2
722      ilwb=1 !2
723      linear=.true.       
724      ncouche=3
725      alphan=0.4
726      semi=0
727
728!     BUT people working hard on the LW may want to read them in 'radia.def'
729!     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
730
731      OPEN(99,file='radia.def',status='old',form='formatted'
732     .     ,iostat=ierr)
733      IF(ierr.EQ.0) THEN
734         write(*,*) 'conf_phys: Reading radia.def !!!'
735         READ(99,fmt='(a)') ch1
736         READ(99,*) callemis
737         WRITE(*,8000) ch1,callemis
738
739         READ(99,fmt='(a)') ch1
740         READ(99,*) iradia
741         WRITE(*,8001) ch1,iradia
742
743         READ(99,fmt='(a)') ch1
744         READ(99,*) ilwd
745         WRITE(*,8001) ch1,ilwd
746
747         READ(99,fmt='(a)') ch1
748         READ(99,*) ilwn
749         WRITE(*,8001) ch1,ilwn
750
751         READ(99,fmt='(a)') ch1
752         READ(99,*) linear
753         WRITE(*,8000) ch1,linear
754
755         READ(99,fmt='(a)') ch1
756         READ(99,*) ncouche
757         WRITE(*,8001) ch1,ncouche
758
759         READ(99,fmt='(a)') ch1
760         READ(99,*) alphan
761         WRITE(*,*) ch1,alphan
762
763         READ(99,fmt='(a)') ch1
764         READ(99,*) ilwb
765         WRITE(*,8001) ch1,ilwb
766
767
768         READ(99,fmt='(a)') ch1
769         READ(99,'(l1)') callg2d
770         WRITE(*,8000) ch1,callg2d
771
772         READ(99,fmt='(a)') ch1
773         READ(99,*) semi
774         WRITE(*,*) ch1,semi
775      end if
776      CLOSE(99)
777
778      END
Note: See TracBrowser for help on using the repository browser.