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

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

LMDZ.MARS. Filling geom arrays is now out of phys_var_state_init. Done through a merged function ini_fillgeom within the comgeomfi_h module. Cosmetic changes. New interface with the mesoscale model: lesser amount of dirty MESOSCALE includes.

File size: 24.3 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. (.not. calladj)) then
227          print*,'Convadj has to be activated when using thermals'
228          stop
229         endif
230
231         write(*,*) "call Richardson-based surface layer ?"
232         callrichsl=.false. ! default value
233         call getin("callrichsl",callrichsl)
234         write(*,*) " callrichsl = ",callrichsl
235
236         if (calltherm .and. .not.callrichsl) then
237          print*,'WARNING WARNING WARNING'
238          print*,'if calltherm=T we strongly advise that '
239          print*,'you use the new surface layer scheme '
240          print*,'by setting callrichsl=T '
241         endif
242
243         if (calladj .and. callrichsl .and. (.not. calltherm)) then
244          print*,'You should not be calling the convective adjustment
245     & scheme with the Richardson surface-layer and without the thermals
246     &. This approach is not
247     & physically consistent and can lead to unrealistic friction
248     & values.'
249          print*,'If you want to use the Ri. surface-layer, either
250     & activate thermals OR de-activate the convective adjustment.'
251          stop
252         endif
253
254         write(*,*) "call CO2 condensation ?"
255         callcond=.true. ! default value
256         call getin("callcond",callcond)
257         write(*,*) " callcond = ",callcond
258
259         write(*,*)"call thermal conduction in the soil ?"
260         callsoil=.true. ! default value
261         call getin("callsoil",callsoil)
262         write(*,*) " callsoil = ",callsoil
263         
264
265         write(*,*)"call Lott's gravity wave/subgrid topography ",
266     &             "scheme ?"
267         calllott=.true. ! default value
268         call getin("calllott",calllott)
269         write(*,*)" calllott = ",calllott
270
271
272         write(*,*)"rad.transfer is computed every iradia",
273     &             " physical timestep"
274         iradia=1 ! default value
275         call getin("iradia",iradia)
276         write(*,*)" iradia = ",iradia
277         
278
279         write(*,*)"Output of the exchange coefficient mattrix ?",
280     &             "(for diagnostics only)"
281         callg2d=.false. ! default value
282         call getin("callg2d",callg2d)
283         write(*,*)" callg2d = ",callg2d
284
285         write(*,*)"Rayleigh scattering : (should be .false. for now)"
286         rayleigh=.false.
287         call getin("rayleigh",rayleigh)
288         write(*,*)" rayleigh = ",rayleigh
289
290
291! TRACERS:
292
293! dustbin
294         write(*,*)"Transported dust ? (if >0, use 'dustbin' dust bins)"
295         dustbin=0 ! default value
296         call getin("dustbin",dustbin)
297         write(*,*)" dustbin = ",dustbin
298! active
299         write(*,*)"Radiatively active dust ? (matters if dustbin>0)"
300         active=.false. ! default value
301         call getin("active",active)
302         write(*,*)" active = ",active
303
304! Test of incompatibility:
305! if active is used, then dustbin should be > 0
306
307         if (active.and.(dustbin.lt.1)) then
308           print*,'if active is used, then dustbin should > 0'
309           stop
310         endif
311! doubleq
312         write(*,*)"use mass and number mixing ratios to predict",
313     &             " dust size ?"
314         doubleq=.false. ! default value
315         call getin("doubleq",doubleq)
316         write(*,*)" doubleq = ",doubleq
317! submicron
318         submicron=.false. ! default value
319         call getin("submicron",submicron)
320         write(*,*)" submicron = ",submicron
321
322! Test of incompatibility:
323! if doubleq is used, then dustbin should be 2
324
325         if (doubleq.and.(dustbin.ne.2)) then
326           print*,'if doubleq is used, then dustbin should be 2'
327           stop
328         endif
329         if (doubleq.and.submicron.and.(nq.LT.3)) then
330           print*,'If doubleq is used with a submicron tracer,'
331           print*,' then the number of tracers has to be'
332           print*,' larger than 3.'
333           stop
334         endif
335
336! lifting
337         write(*,*)"dust lifted by GCM surface winds ?"
338         lifting=.false. ! default value
339         call getin("lifting",lifting)
340         write(*,*)" lifting = ",lifting
341
342! Test of incompatibility:
343! if lifting is used, then dustbin should be > 0
344
345         if (lifting.and.(dustbin.lt.1)) then
346           print*,'if lifting is used, then dustbin should > 0'
347           stop
348         endif
349
350! free evolving dust
351! freedust=true just says that there is no lifting and no dust opacity scaling.
352         write(*,*)"dust lifted by GCM surface winds ?"
353         freedust=.false. ! default value
354         call getin("freedust",freedust)
355         write(*,*)" freedust = ",freedust
356         if (freedust.and..not.doubleq) then
357           print*,'freedust should be used with doubleq !'
358           stop
359         endif
360         if (freedust.and.lifting) then
361           print*,'if freedust is used, then lifting should not be used'
362           print*,'lifting forced to false !!'
363           lifting=.false.
364         endif
365
366! callddevil
367         write(*,*)" dust lifted by dust devils ?"
368         callddevil=.false. !default value
369         call getin("callddevil",callddevil)
370         write(*,*)" callddevil = ",callddevil
371
372! Test of incompatibility:
373! if dustdevil is used, then dustbin should be > 0
374
375         if (callddevil.and.(dustbin.lt.1)) then
376           print*,'if dustdevil is used, then dustbin should > 0'
377           stop
378         endif
379! sedimentation
380         write(*,*) "Gravitationnal sedimentation ?"
381         sedimentation=.true. ! default value
382         call getin("sedimentation",sedimentation)
383         write(*,*) " sedimentation = ",sedimentation
384! activice
385         write(*,*) "Radiatively active transported atmospheric ",
386     &              "water ice ?"
387         activice=.false. ! default value
388         call getin("activice",activice)
389         write(*,*) " activice = ",activice
390! water
391         write(*,*) "Compute water cycle ?"
392         water=.false. ! default value
393         call getin("water",water)
394         write(*,*) " water = ",water
395
396! thermal inertia feedback
397         write(*,*) "Activate the thermal inertia feedback ?"
398         tifeedback=.false. ! default value
399         call getin("tifeedback",tifeedback)
400         write(*,*) " tifeedback = ",tifeedback
401
402! Test of incompatibility:
403
404         if (tifeedback.and..not.water) then
405           print*,'if tifeedback is used,'
406           print*,'water should be used too'
407           stop
408         endif
409
410         if (tifeedback.and..not.callsoil) then
411           print*,'if tifeedback is used,'
412           print*,'callsoil should be used too'
413           stop
414         endif
415
416         if (activice.and..not.water) then
417           print*,'if activice is used, water should be used too'
418           stop
419         endif
420
421         if (water.and..not.tracer) then
422           print*,'if water is used, tracer should be used too'
423           stop
424         endif
425         
426! water ice clouds effective variance distribution for sedimentaion       
427        write(*,*) "effective variance for water ice clouds ?"
428        nuice_sed=0.45
429        call getin("nuice_sed",nuice_sed)
430        write(*,*) "water_param nueff Sedimentation:", nuice_sed
431         
432! ccn factor if no scavenging         
433        write(*,*) "water param CCN reduc. factor ?", ccn_factor
434        ccn_factor = 4.5
435        call getin("ccn_factor",ccn_factor)
436        write(*,*)" ccn_factor = ",ccn_factor
437        write(*,*)"Careful: only used when microphys=F, otherwise"
438        write(*,*)"the contact parameter is used instead;"
439
440! microphys
441         write(*,*)"Microphysical scheme for water-ice clouds?"
442         microphys=.false. ! default value
443         call getin("microphys",microphys)
444         write(*,*)" microphys = ",microphys
445
446! microphysical parameter contact       
447         write(*,*) "water contact parameter ?"
448         mteta  = 0.95
449         call getin("mteta",mteta)
450         write(*,*) "mteta = ", mteta
451
452! scavenging
453         write(*,*)"Dust scavenging by H2O/CO2 snowfall ?"
454         scavenging=.false. ! default value
455         call getin("scavenging",scavenging)
456         write(*,*)" scavenging = ",scavenging
457         
458
459! Test of incompatibility:
460! if scavenging is used, then dustbin should be > 0
461
462         if ((microphys.and..not.doubleq).or.
463     &       (microphys.and..not.water)) then
464             print*,'if microphys is used, then doubleq,'
465             print*,'and water must be used!'
466             stop
467         endif
468         if (microphys.and..not.scavenging) then
469             print*,''
470             print*,'----------------WARNING-----------------'
471             print*,'microphys is used without scavenging !!!'
472             print*,'----------------WARNING-----------------'
473             print*,''
474         endif
475
476         if ((scavenging.and..not.microphys).or.
477     &       (scavenging.and.(dustbin.lt.1))) then
478             print*,'if scavenging is used, then microphys'
479             print*,'must be used!'
480             stop
481         endif
482
483! Test of incompatibility:
484
485         write(*,*) "Permanent water caps at poles ?",
486     &               " .true. is RECOMMENDED"
487         write(*,*) "(with .true., North cap is a source of water ",
488     &   "and South pole is a cold trap)"
489         caps=.true. ! default value
490         call getin("caps",caps)
491         write(*,*) " caps = ",caps
492
493! albedo_h2o_ice
494         write(*,*) "water ice albedo ?"
495         albedo_h2o_ice=0.45
496         call getin("albedo_h2o_ice",albedo_h2o_ice)
497         write(*,*) " albedo_h2o_ice = ",albedo_h2o_ice
498! inert_h2o_ice
499         write(*,*) "water ice thermal inertia ?"
500         inert_h2o_ice=2400 ! (J.m^-2.K^-1.s^-1/2)
501         call getin("inert_h2o_ice",inert_h2o_ice)
502         write(*,*) " inert_h2o_ice = ",inert_h2o_ice
503! frost_albedo_threshold
504         write(*,*) "frost thickness threshold for albedo ?"
505         frost_albedo_threshold=0.005 ! 5.4 mic (i.e 0.005 kg.m-2)
506         call getin("frost_albedo_threshold",
507     &    frost_albedo_threshold)
508         write(*,*) " frost_albedo_threshold = ",
509     &            frost_albedo_threshold
510
511! call Titus crocus line -- DEFAULT IS NONE
512         write(*,*) "Titus crocus line ?"
513         tituscap=.false.  ! default value
514         call getin("tituscap",tituscap)
515         write(*,*) "tituscap",tituscap
516                     
517
518         write(*,*) "photochemistry: include chemical species"
519         photochem=.false. ! default value
520         call getin("photochem",photochem)
521         write(*,*) " photochem = ",photochem
522
523
524! THERMOSPHERE
525
526         write(*,*) "call thermosphere ?"
527         callthermos=.false. ! default value
528         call getin("callthermos",callthermos)
529         write(*,*) " callthermos = ",callthermos
530         
531
532         write(*,*) " water included without cycle ",
533     &              "(only if water=.false.)"
534         thermoswater=.false. ! default value
535         call getin("thermoswater",thermoswater)
536         write(*,*) " thermoswater = ",thermoswater
537
538         write(*,*) "call thermal conduction ?",
539     &    " (only if callthermos=.true.)"
540         callconduct=.false. ! default value
541         call getin("callconduct",callconduct)
542         write(*,*) " callconduct = ",callconduct
543
544         write(*,*) "call EUV heating ?",
545     &   " (only if callthermos=.true.)"
546         calleuv=.false.  ! default value
547         call getin("calleuv",calleuv)
548         write(*,*) " calleuv = ",calleuv
549
550         write(*,*) "call molecular viscosity ?",
551     &   " (only if callthermos=.true.)"
552         callmolvis=.false. ! default value
553         call getin("callmolvis",callmolvis)
554         write(*,*) " callmolvis = ",callmolvis
555
556         write(*,*) "call molecular diffusion ?",
557     &   " (only if callthermos=.true.)"
558         callmoldiff=.false. ! default value
559         call getin("callmoldiff",callmoldiff)
560         write(*,*) " callmoldiff = ",callmoldiff
561         
562
563         write(*,*) "call thermospheric photochemistry ?",
564     &   " (only if callthermos=.true.)"
565         thermochem=.false. ! default value
566         call getin("thermochem",thermochem)
567         write(*,*) " thermochem = ",thermochem
568
569         write(*,*) "Method to include solar variability"
570         write(*,*) "0-> old method (using solarcondate); ",
571     &                  "1-> variability wit E10.7"
572         solvarmod=1
573         call getin("solvarmod",solvarmod)
574         write(*,*) " solvarmod = ",solvarmod
575
576         write(*,*) "date for solar flux calculation:",
577     &   " (1985 < date < 2002)",
578     $   " (Only used if solvarmod=0)"
579         write(*,*) "(Solar min=1996.4 ave=1993.4 max=1990.6)"
580         solarcondate=1993.4 ! default value
581         call getin("solarcondate",solarcondate)
582         write(*,*) " solarcondate = ",solarcondate
583         
584         write(*,*) "Solar variability as observed for MY: "
585         write(*,*) "Only if solvarmod=1"
586         solvaryear=24
587         call getin("solvaryear",solvaryear)
588         write(*,*) " solvaryear = ",solvaryear
589
590         write(*,*) "UV heating efficiency:",
591     &   "measured values between 0.19 and 0.23 (Fox et al. 1996)",
592     &   "lower values may be used to compensate low 15 um cooling"
593         euveff=0.21 !default value
594         call getin("euveff",euveff)
595         write(*,*) " euveff = ", euveff
596
597         if (.not.callthermos) then
598           if (thermoswater) then
599             print*,'if thermoswater is set, callthermos must be true'
600             stop
601           endif         
602           if (callconduct) then
603             print*,'if callconduct is set, callthermos must be true'
604             stop
605           endif       
606           if (calleuv) then
607             print*,'if calleuv is set, callthermos must be true'
608             stop
609           endif         
610           if (callmolvis) then
611             print*,'if callmolvis is set, callthermos must be true'
612             stop
613           endif       
614           if (callmoldiff) then
615             print*,'if callmoldiff is set, callthermos must be true'
616             stop
617           endif         
618           if (thermochem) then
619             print*,'if thermochem is set, callthermos must be true'
620             stop
621           endif         
622        endif
623
624! Test of incompatibility:
625! if photochem is used, then water should be used too
626
627         if (photochem.and..not.water) then
628           print*,'if photochem is used, water should be used too'
629           stop
630         endif
631
632! if callthermos is used, then thermoswater should be used too
633! (if water not used already)
634
635         if (callthermos .and. .not.water) then
636           if (callthermos .and. .not.thermoswater) then
637             print*,'if callthermos is used, water or thermoswater
638     &               should be used too'
639             stop
640           endif
641         endif
642
643         PRINT*,'--------------------------------------------'
644         PRINT*
645         PRINT*
646      ELSE
647         write(*,*)
648         write(*,*) 'Cannot read file callphys.def. Is it here ?'
649         stop
650      ENDIF
651
6528000  FORMAT(t5,a12,l8)
6538001  FORMAT(t5,a12,i8)
654
655      PRINT*
656      PRINT*,'conf_phys: daysec',daysec
657      PRINT*
658      PRINT*,'conf_phys: The radiative transfer is computed:'
659      PRINT*,'           each ',iradia,' physical time-step'
660      PRINT*,'        or each ',iradia*dtphys,' seconds'
661      PRINT*
662! --------------------------------------------------------------
663!  Managing the Longwave radiative transfer
664! --------------------------------------------------------------
665
666!     In most cases, the run just use the following values :
667!     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
668      callemis=.true.     
669!     ilwd=10*int(daysec/dtphys) ! bug before 22/10/01       
670      ilwd=1
671      ilwn=1 !2
672      ilwb=1 !2
673      linear=.true.       
674      ncouche=3
675      alphan=0.4
676      semi=0
677
678!     BUT people working hard on the LW may want to read them in 'radia.def'
679!     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
680
681      OPEN(99,file='radia.def',status='old',form='formatted'
682     .     ,iostat=ierr)
683      IF(ierr.EQ.0) THEN
684         write(*,*) 'conf_phys: Reading radia.def !!!'
685         READ(99,fmt='(a)') ch1
686         READ(99,*) callemis
687         WRITE(*,8000) ch1,callemis
688
689         READ(99,fmt='(a)') ch1
690         READ(99,*) iradia
691         WRITE(*,8001) ch1,iradia
692
693         READ(99,fmt='(a)') ch1
694         READ(99,*) ilwd
695         WRITE(*,8001) ch1,ilwd
696
697         READ(99,fmt='(a)') ch1
698         READ(99,*) ilwn
699         WRITE(*,8001) ch1,ilwn
700
701         READ(99,fmt='(a)') ch1
702         READ(99,*) linear
703         WRITE(*,8000) ch1,linear
704
705         READ(99,fmt='(a)') ch1
706         READ(99,*) ncouche
707         WRITE(*,8001) ch1,ncouche
708
709         READ(99,fmt='(a)') ch1
710         READ(99,*) alphan
711         WRITE(*,*) ch1,alphan
712
713         READ(99,fmt='(a)') ch1
714         READ(99,*) ilwb
715         WRITE(*,8001) ch1,ilwb
716
717
718         READ(99,fmt='(a)') ch1
719         READ(99,'(l1)') callg2d
720         WRITE(*,8000) ch1,callg2d
721
722         READ(99,fmt='(a)') ch1
723         READ(99,*) semi
724         WRITE(*,*) ch1,semi
725      end if
726      CLOSE(99)
727
728      END
Note: See TracBrowser for help on using the repository browser.