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

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

LMDZ.MARS
IMPORTANT CHANGE

  • Remove all reference/use of nlayermx and dimphys.h
  • Made use of automatic arrays whenever arrays are needed with dimension nlayer
  • Remove lots of obsolete reference to dimensions.h
  • Converted iono.h and param_v4.h into corresponding modules

(with embedded subroutine to allocate arrays)
(no arrays allocated if thermosphere not used)

  • Deleted param.h and put contents into module param_v4_h
  • Adapted testphys1d, newstart, etc...
  • Made DATA arrays in param_read to be initialized by subroutine

fill_data_thermos in module param_v4_h

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