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

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

LMDZ.MARS : Replaced comcstfi and planete includes by modules.

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