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

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

LMDZ.MARS made a mistake in previous commit. corrected.

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