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

Last change on this file since 3144 was 3144, checked in by jliu, 15 months ago

Mars PCM
New scheme "nonoro_gwd_mix_mod" to simulate non-orographic gravity waves induced mixing. The scheme flag "calljliu_gwimix" has been put to "false" as default.
There are three tunable parameters that have been set up, as "nonoro_gwimixing_eff=0.1", "nonoro_gwimixing_eff1=0.1", "nonoro_gwimixing_vdl=1.5".
Remember to use full-layers model configuration (64x48x73) when you try to call this scheme because we need to evaluate the saturation altitude of each monochromatic wave.
More than ~75% of the waves saturated at altitude above 120 km.
Jliu

File size: 47.4 KB
Line 
1      MODULE conf_phys_mod
2     
3      IMPLICIT NONE
4     
5      CONTAINS
6
7      SUBROUTINE conf_phys(ngrid,nlayer,nq)
8 
9!=======================================================================
10!
11!   purpose:
12!   -------
13!
14!   Initialisation for the physical parametrisations
15!   flags (i.e. run-time options) of the Mars PCM
16!-----------------------------------------------------------------------
17
18      USE ioipsl_getin_p_mod, ONLY : getin_p
19      use tracer_mod, only : nuice_sed, ccn_factor, nuiceco2_sed,
20     &                       nuice_ref,nuiceco2_ref
21      use surfdat_h, only: albedo_h2o_cap,albedo_h2o_frost,
22     &                     frost_albedo_threshold, inert_h2o_ice,
23     &                     frost_metam_threshold,old_wsublimation_scheme
24      use time_phylmdz_mod, only: ecritphy,day_step,iphysiq,ecritstart,
25     &                            daysec,dtphys
26      use dimradmars_mod, only: naerkind, name_iaer,
27     &                      ini_scatterers,tauvis
28      use datafile_mod, only: datadir
29      use wstats_mod, only: callstats
30      use writediagsoil_mod, only: diagsoil
31      use calchim_mod, only: ichemistry
32      use co2condens_mod, only: scavco2cond
33      use dust_param_mod, only: dustbin, doubleq, submicron, active,
34     &                          lifting, freedust, callddevil,
35     &                          dustscaling_mode,
36     &                          reff_driven_IRtoVIS_scenario
37      use aeropacity_mod, only: iddist, topdustref
38      USE mod_phys_lmdz_transfert_para, ONLY: bcast
39      USE paleoclimate_mod,ONLY: paleoclimate,albedo_perennialco2,
40     &                           lag_layer
41      use microphys_h, only: mteta
42      use comsoil_h, only: adsorption_soil, choice_ads
43      use nonoro_gwd_mix_mod, only: calljliu_gwimix
44
45      IMPLICIT NONE
46
47      include "callkeys.h"
48
49      INTEGER,INTENT(IN) :: ngrid ! number of atmospheric columns
50      INTEGER,INTENT(IN) :: nlayer ! number of atmospheric layers
51      INTEGER,INTENT(IN) :: nq ! number of tracers
52
53      INTEGER ierr,j
54      character(len=20),parameter :: modname="conf_phys"
55 
56      CHARACTER ch1*12
57#ifndef MESOSCALE
58      ! read in some parameters from "run.def" for physics,
59      ! or shared between dynamics and physics.
60      ecritphy=240 ! default value
61      call getin_p("ecritphy",ecritphy) ! frequency of outputs in physics,
62                                      ! in dynamical steps
63      day_step=960 ! default value
64      call getin_p("day_step",day_step) ! number of dynamical steps per day
65      iphysiq=20 ! default value
66      call getin_p("iphysiq",iphysiq) ! call physics every iphysiq dyn step
67      ecritstart=0 ! default value
68      call getin_p("ecritstart",ecritstart) ! write a restart every ecristart steps
69#endif
70
71! --------------------------------------------------------------
72!  Reading the "callphys.def" file controlling some key options
73! --------------------------------------------------------------
74     
75!$OMP MASTER
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!$OMP END MASTER
81      call bcast(ierr)
82!       ierr=0
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         ! default path is set in datafile_mod
93         call getin_p("datadir",datadir)
94         write(*,*) " datadir = ",trim(datadir)
95
96         write(*,*) "Initialize physics with startfi.nc file ?"
97         startphy_file=.true.
98         call getin_p("startphy_file",startphy_file)
99         write(*,*) "startphy_file", startphy_file
100         
101         write(*,*) "Diurnal cycle ?"
102         write(*,*) "(if diurnal=False, diurnal averaged solar heating)"
103         diurnal=.true. ! default value
104         call getin_p("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_p("season",season)
112         write(*,*) " season = ",season
113
114         write(*,*) "Write some extra output to the screen ?"
115         lwrite=.false. ! default value
116         call getin_p("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_p("callstats",callstats)
126         write(*,*) " callstats = ",callstats
127
128         write(*,*) "Write sub-surface fields in file diagsoil.nc ?"
129         diagsoil=.false. ! default value
130         call getin_p("diagsoil",diagsoil)
131         write(*,*) " diagsoil = ",diagsoil
132         
133         write(*,*) "Save EOF profiles in file 'profiles' for ",
134     &              "Climate Database?"
135         calleofdump=.false. ! default value
136         call getin_p("calleofdump",calleofdump)
137         write(*,*) " calleofdump = ",calleofdump
138
139         write(*,*) "Dust scenario: 1=constant dust (read from startfi",
140     &   " or set as tauvis); 2=Viking scenario; =3 MGS scenario,",
141     &   "=6 cold (low dust) scenario; =7 warm (high dust) scenario ",
142     &   "=24,25 ... 30 :Mars Year 24, ... or 30 from TES assimilation"
143         iaervar=3 ! default value
144         call getin_p("iaervar",iaervar)
145         write(*,*) " iaervar = ",iaervar
146
147         write(*,*) "Reference (visible) dust opacity at 610 Pa ",
148     &   "(matters only if iaervar=1)"
149         ! NB: default value of tauvis is set/read in startfi.nc file
150         call getin_p("tauvis",tauvis)
151         write(*,*) " tauvis = ",tauvis
152
153         write(*,*) "Dust vertical distribution:"
154         write(*,*) "(=1 top set by topdustref parameter;",
155     & " =2 Viking scenario; =3 MGS scenario)"
156         iddist=3 ! default value
157         call getin_p("iddist",iddist)
158         write(*,*) " iddist = ",iddist
159
160         write(*,*) "Dust top altitude (km). (Matters only if iddist=1)"
161         topdustref= 90.0 ! default value
162         call getin_p("topdustref",topdustref)
163         write(*,*) " topdustref = ",topdustref
164
165         write(*,*) "Prescribed surface thermal flux (H/(rho*cp),K m/s)"
166         tke_heat_flux=0. ! default value
167         call getin_p("tke_heat_flux",tke_heat_flux)
168         write(*,*) " tke_heat_flux = ",tke_heat_flux
169         write(*,*) " 0 means the usual schemes are computing"
170
171         write(*,*) "call radiative transfer ?"
172         callrad=.true. ! default value
173         call getin_p("callrad",callrad)
174         write(*,*) " callrad = ",callrad
175
176         write(*,*) "call slope insolation scheme ?",
177     &              "(matters only if callrad=T)"
178#ifdef MESOSCALE
179         callslope=.true. ! default value
180#else
181         callslope=.false. ! default value (not supported yet)
182#endif
183         call getin_p("callslope",callslope)
184         write(*,*) " callslope = ",callslope
185
186         write(*,*) "call NLTE radiative schemes ?",
187     &              "(matters only if callrad=T)"
188         callnlte=.false. ! default value
189         call getin_p("callnlte",callnlte)
190         write(*,*) " callnlte = ",callnlte
191         
192         nltemodel=0    !default value
193         write(*,*) "NLTE model?"
194         write(*,*) "0 -> old model, static O"
195         write(*,*) "1 -> old model, dynamic O"
196         write(*,*) "2 -> new model"
197         write(*,*) "(matters only if callnlte=T)"
198         call getin_p("nltemodel",nltemodel)
199         write(*,*) " nltemodel = ",nltemodel
200
201         write(*,*) "call CO2 NIR absorption ?",
202     &              "(matters only if callrad=T)"
203         callnirco2=.false. ! default value
204         call getin_p("callnirco2",callnirco2)
205         write(*,*) " callnirco2 = ",callnirco2
206
207         write(*,*) "New NIR NLTE correction ?",
208     $              "0-> old model (no correction)",
209     $              "1-> new correction",
210     $              "(matters only if callnirco2=T)"
211#ifdef MESOSCALE
212         nircorr=0      !default value. this is OK below 60 km.
213#else
214         nircorr=0      !default value
215#endif
216         call getin_p("nircorr",nircorr)
217         write(*,*) " nircorr = ",nircorr
218
219         write(*,*) "call turbulent vertical diffusion ?"
220         calldifv=.true. ! default value
221         call getin_p("calldifv",calldifv)
222         write(*,*) " calldifv = ",calldifv
223
224         write(*,*) "call thermals ?"
225         calltherm=.false. ! default value
226         call getin_p("calltherm",calltherm)
227         write(*,*) " calltherm = ",calltherm
228
229         write(*,*) "call convective adjustment ?"
230         calladj=.true. ! default value
231         call getin_p("calladj",calladj)
232         write(*,*) " calladj = ",calladj
233
234         if (calltherm .and. calladj) then
235          print*,'!!! PLEASE NOTE !!!'
236          print*,'convective adjustment is on'
237          print*,'but since thermal plume model is on'
238          print*,'convadj is only activated above the PBL'
239         endif
240       
241         write(*,*) "used latest version of yamada scheme?"
242         callyamada4=.true. ! default value
243         call getin_p("callyamada4",callyamada4)
244         write(*,*) " callyamada4 = ",callyamada4
245
246         if (calltherm .and. .not.callyamada4) then
247          print*,'!!!! WARNING WARNING WARNING !!!!'
248          print*,'if calltherm=T we strongly advise that '
249          print*,'you set the flag callyamada4 to T '
250          print*,'!!!! WARNING WARNING WARNING !!!!'
251         endif
252 
253         write(*,*) "call Richardson-based surface layer ?"
254         callrichsl=.false. ! default value
255         call getin_p("callrichsl",callrichsl)
256         write(*,*) " callrichsl = ",callrichsl
257
258         if (calltherm .and. .not.callrichsl) then
259          print*,'WARNING WARNING WARNING'
260          print*,'if calltherm=T we strongly advise that '
261          print*,'you use the new surface layer scheme '
262          print*,'by setting callrichsl=T '
263         endif
264
265         if (calladj .and. callrichsl .and. (.not. calltherm)) then
266          print*,'You should not be calling the convective adjustment
267     & scheme with the Richardson surface-layer and without the thermals
268     &. This approach is not
269     & physically consistent and can lead to unrealistic friction
270     & values.'
271          print*,'If you want to use the Ri. surface-layer, either
272     & activate thermals OR de-activate the convective adjustment.'
273          call abort_physic(modname,
274     &     "Richardson layer must be used with thermals",1)
275         endif
276
277         write(*,*) "call CO2 condensation ?"
278         callcond=.true. ! default value
279         call getin_p("callcond",callcond)
280         write(*,*) " callcond = ",callcond
281
282         write(*,*)"call thermal conduction in the soil ?"
283         callsoil=.true. ! default value
284         call getin_p("callsoil",callsoil)
285         write(*,*) " callsoil = ",callsoil
286         
287
288         write(*,*)"call Lott's gravity wave/subgrid topography ",
289     &             "scheme ?"
290         calllott=.true. ! default value
291         call getin_p("calllott",calllott)
292         write(*,*)" calllott = ",calllott
293
294         write(*,*)"call Lott's non-oro GWs parameterisation ",
295     &             "scheme ?"
296         calllott_nonoro=.false. ! default value
297         call getin_p("calllott_nonoro",calllott_nonoro)
298         write(*,*)" calllott_nonoro = ",calllott_nonoro
299
300         write(*,*)"call jliu's nonoro GWs-induced mixing ",
301     &             "scheme ?"
302         calljliu_gwimix=.false. ! default value
303         call getin_p("calljliu_gwimix",calljliu_gwimix)
304         write(*,*)" calljliu_gwimix = ",calljliu_gwimix
305
306
307! rocket dust storm injection scheme
308         write(*,*)"call rocket dust storm parametrization"
309         rdstorm=.false. ! default value
310         call getin_p("rdstorm",rdstorm)
311         write(*,*)" rdstorm = ",rdstorm
312! rocket dust storm detrainment coefficient       
313        coeff_detrainment=0.02 ! default value
314        call getin_p("coeff_detrainment",coeff_detrainment)
315        write(*,*)" coeff_detrainment = ",coeff_detrainment
316
317! entrainment by mountain top dust flows scheme
318         write(*,*)"call mountain top dust flows parametrization"
319         topflows=.false. ! default value
320         call getin_p("topflows",topflows)
321         write(*,*)" topflows = ",topflows
322
323! latent heat release from ground water ice sublimation/condensation
324         write(*,*)"latent heat release during sublimation",
325     &              " /condensation of ground water ice"
326         latentheat_surfwater=.true. ! default value
327         call getin_p("latentheat_surfwater",latentheat_surfwater)
328         write(*,*)" latentheat_surfwater = ",latentheat_surfwater
329
330         write(*,*)"rad.transfer is computed every iradia",
331     &             " physical timestep"
332         iradia=1 ! default value
333         call getin_p("iradia",iradia)
334         write(*,*)" iradia = ",iradia
335         
336
337         write(*,*)"Output of the exchange coefficient mattrix ?",
338     &             "(for diagnostics only)"
339         callg2d=.false. ! default value
340         call getin_p("callg2d",callg2d)
341         write(*,*)" callg2d = ",callg2d
342
343         write(*,*)"Rayleigh scattering : (should be .false. for now)"
344         rayleigh=.false.
345         call getin_p("rayleigh",rayleigh)
346         write(*,*)" rayleigh = ",rayleigh
347
348! PALEOCLIMATE
349
350         write(*,*)"Using lag layer??"
351         lag_layer=.false.
352         call getin_p("lag_layer",lag_layer)
353         write(*,*) " lag_layer = ", lag_layer
354
355        write(*,*)"Is it paleoclimate run?"
356         paleoclimate=.false. ! default value
357         call getin_p("paleoclimate",paleoclimate)
358         write(*,*)" paleoclimate = ",paleoclimate
359
360
361         write(*,*)"Albedo for perennial CO2 ice?"
362         albedo_perennialco2 = 0.85 ! default value
363         call getin_p("albedo_perennialco2",albedo_perennialco2)
364         write(*,*)"albedo_perennialco2 = ",albedo_perennialco2
365
366! TRACERS:
367
368! dustbin
369         write(*,*)"Transported dust ? (if >0, use 'dustbin' dust bins)"
370         dustbin=0 ! default value
371         call getin_p("dustbin",dustbin)
372         write(*,*)" dustbin = ",dustbin
373! active
374         write(*,*)"Radiatively active dust ? (matters if dustbin>0)"
375         active=.false. ! default value
376         call getin_p("active",active)
377         write(*,*)" active = ",active
378
379! Test of incompatibility:
380! if active is used, then dustbin should be > 0
381
382         if (active.and.(dustbin.lt.1)) then
383           print*,'if active is used, then dustbin should > 0'
384           call abort_physic(modname,
385     &          "active option requires dustbin < 0",1)
386         endif
387! doubleq
388         write(*,*)"use mass and number mixing ratios to predict",
389     &             " dust size ?"
390         doubleq=.false. ! default value
391         call getin_p("doubleq",doubleq)
392         write(*,*)" doubleq = ",doubleq
393! submicron
394         submicron=.false. ! default value
395         call getin_p("submicron",submicron)
396         write(*,*)" submicron = ",submicron
397
398! Test of incompatibility:
399! if doubleq is used, then dustbin should be 2
400
401         if (doubleq.and.(dustbin.ne.2)) then
402           print*,'if doubleq is used, then dustbin should be 2'
403           call abort_physic(modname,
404     &          "doubleq option requires dustbin = 2",1)
405         endif
406         if (doubleq.and.submicron.and.(nq.LT.3)) then
407           print*,'If doubleq is used with a submicron tracer,'
408           print*,' then the number of tracers has to be'
409           print*,' larger than 3.'
410           call abort_physic(modname,
411     &          "submicron option requires dustbin > 2",1)
412         endif
413
414! lifting
415         write(*,*)"dust lifted by GCM surface winds ?"
416         lifting=.false. ! default value
417         call getin_p("lifting",lifting)
418         write(*,*)" lifting = ",lifting
419
420! Test of incompatibility:
421! if lifting is used, then dustbin should be > 0
422
423         if (lifting.and.(dustbin.lt.1)) then
424           print*,'if lifting is used, then dustbin should > 0'
425           call abort_physic(modname,
426     &          "lifting option requires dustbin > 0",1)
427         endif
428
429! dust injection scheme
430        dustinjection=0 ! default: no injection scheme
431        call getin_p("dustinjection",dustinjection)
432        write(*,*)" dustinjection = ",dustinjection
433! dust injection scheme coefficient       
434        coeff_injection=0.25 ! default value
435        call getin_p("coeff_injection",coeff_injection)
436        write(*,*)" coeff_in,jection = ",coeff_injection
437! timing for dust injection       
438        ti_injection=0. ! default value
439        tf_injection=24. ! default value
440        call getin_p("ti_injection",ti_injection)
441        write(*,*)" ti_injection = ",ti_injection
442        call getin_p("tf_injection",tf_injection)
443        write(*,*)" tf_injection = ",tf_injection
444
445! free evolving dust
446! freedust=true just says that there is no lifting and no dust opacity scaling.
447         write(*,*)"dust lifted by GCM surface winds ?"
448         freedust=.false. ! default value
449         call getin_p("freedust",freedust)
450         write(*,*)" freedust = ",freedust
451         if (freedust.and..not.doubleq) then
452           print*,'freedust should be used with doubleq !'
453           call abort_physic(modname,
454     &          "freedust option requires doubleq",1)
455         endif
456
457! dust rescaling mode (if any)
458!     =0 --> freedust, tauscaling=1
459!     =1 --> GCM5.3-like, tauscaling computed wrt tau_pref_scenario
460!     =2 --> tauscaling=1 but dust_rad_adjust (rescaling for the radiative transfer only)
461         if (freedust) then
462           dustscaling_mode=0
463         else
464           dustscaling_mode=1 ! GCMv5.3 style
465         endif
466         call getin_p("dustscaling_mode",dustscaling_mode)
467         write(*,*) "dustscaling_mode=",dustscaling_mode
468         if ((dustscaling_mode.eq.1).and.freedust) then
469           print*,'freedust and dustscaling_mode=1 are incompatible !'
470           call abort_physic(modname,
471     &          "freedust and dustscaling_mode=1 are incompatible",1)
472         endif         
473
474#ifndef MESOSCALE
475         ! this test is valid in GCM case
476         ! ... not in mesoscale case, for we want to activate mesoscale lifting
477         if (freedust.and.dustinjection.eq.0)then
478           if(lifting) then
479             print*,'if freedust is used and dustinjection = 0,
480     &      then lifting should not be used'
481             call abort_physic(modname,
482     &          "freedust option with dustinjection = 0"//
483     &          " requires lifting to be false",1)
484           endif
485         endif
486#endif
487         if (dustinjection.eq.1)then
488           if(.not.lifting) then
489             print*,"if dustinjection=1, then lifting should be true"
490             call abort_physic(modname,
491     &          "dustinjection=1 requires lifting",1)
492           endif
493           if(.not.freedust) then
494             print*,"if dustinjection=1, then freedust should be true"
495             call abort_physic(modname,
496     &          "dustinjection=1 requires freedust",1)
497           endif
498         endif
499! rocket dust storm and entrainment by top flows
500! Test of incompatibility:
501! if rdstorm or topflows is used, then doubleq should be true
502         if ((rdstorm.or.topflows).and..not.doubleq) then
503           print*,'if rdstorm or topflows is used, then doubleq
504     &            should be used !'
505           call abort_physic(modname,
506     &          "rdstorm or topflows requires doubleq",1)
507         endif
508         if ((rdstorm.or.topflows).and..not.active) then
509           print*,'if rdstorm or topflows is used, then active
510     &            should be used !'
511           call abort_physic(modname,
512     &          "rdstorm or topflows requires active",1)
513         endif
514         if (rdstorm.and..not.lifting) then
515           print*,'if rdstorm is used, then lifting
516     &            should be used !'
517           call abort_physic(modname,
518     &          "rdstorm requires lifting",1)
519         endif
520         if ((rdstorm.or.topflows).and..not.freedust) then
521           print*,'if rdstorm or topflows is used, then freedust
522     &            should be used !'
523           call abort_physic(modname,
524     &          "rdstorm or topflows requires freedust",1)
525         endif
526         if (rdstorm.and.(dustinjection.eq.0)) then
527           print*,'if rdstorm is used, then dustinjection
528     &            should be used !'
529           call abort_physic(modname,
530     &          "rdstorm requires dustinjection",1)
531         endif
532! Dust IR opacity
533         write(*,*)" Wavelength for infrared opacity of dust ?"
534         write(*,*)" Choices are:"
535         write(*,*)" tes  --- > 9.3 microns  [default]"
536         write(*,*)" mcs  --- > 21.6 microns"
537         !
538         ! WARNING WARNING WARNING WARNING WARNING WARNING
539         !
540         ! BEFORE ADDING A NEW VALUE, BE SURE THAT THE
541         ! CORRESPONDING WAVELENGTH IS IN THE LOOKUP TABLE,
542         ! OR AT LEAST NO TO FAR, TO AVOID FALLACIOUS INTERPOLATIONS.
543         !
544         dustiropacity="tes" !default value
545         call getin_p("dustiropacity",dustiropacity)
546         write(*,*)" dustiropacity = ",trim(dustiropacity)
547         select case (trim(dustiropacity))
548           case ("tes")
549             dustrefir = 9.3E-6
550           case ("mcs")
551             dustrefir = 21.6E-6
552           case default
553              write(*,*) trim(dustiropacity),
554     &                  " is not a valid option for dustiropacity"
555             call abort_physic(modname,
556     &          "invalid dustiropacity option value",1)
557         end select
558! Dust scenario IR to VIS conversion
559         write(*,*)"Use an IR to VIS conversion coefficient"
560         write(*,*)"for the dust scenario, that is dependent"
561         write(*,*)"on the GCM dust effective radius,"
562         write(*,*)"instead of a fixed 2.6 coefficient ?"
563         reff_driven_IRtoVIS_scenario=.false. !default value
564         call getin_p("reff_driven_IRtoVIS_scenario",
565     &                 reff_driven_IRtoVIS_scenario)
566         write(*,*)" reff_driven_IRtoVIS_scenario = ",
567     &               reff_driven_IRtoVIS_scenario
568! Test of incompatibility:
569! if reff_driven_IRtoVIS_scenario=.true.,
570! dustrefir must be 9.3E-6 = scenarios' wavelength
571         if (reff_driven_IRtoVIS_scenario .and.
572     &      (dustrefir.ne.9.3E-6)) then
573           print*,'if reff_driven_IRtoVIS_scenario is used, then '//
574     &           'the GCM IR reference wavelength should be the one '//
575     &           'of the scenarios (dustiropacity=tes)'
576           call abort_physic(modname,
577     &        "reff_driven_IRtoVIS_scenario requires tes wavelength",1)
578         endif
579
580! callddevil
581         write(*,*)" dust lifted by dust devils ?"
582         callddevil=.false. !default value
583         call getin_p("callddevil",callddevil)
584         write(*,*)" callddevil = ",callddevil
585
586! Test of incompatibility:
587! if dustdevil is used, then dustbin should be > 0
588         if (callddevil.and.(dustbin.lt.1)) then
589           print*,'if dustdevil is used, then dustbin should > 0'
590           call abort_physic(modname,
591     &          "callddevil requires dustbin > 0",1)
592         endif
593         
594! sedimentation
595         write(*,*) "Gravitationnal sedimentation ?"
596         sedimentation=.true. ! default value
597         call getin_p("sedimentation",sedimentation)
598         write(*,*) " sedimentation = ",sedimentation
599! activice
600         write(*,*) "Radiatively active transported atmospheric ",
601     &              "water ice ?"
602         activice=.false. ! default value
603         call getin_p("activice",activice)
604         write(*,*) " activice = ",activice
605! water
606         write(*,*) "Compute water cycle ?"
607         water=.false. ! default value
608         call getin_p("water",water)
609         write(*,*) " water = ",water
610! hdo
611         write(*,*) "Compute hdo cycle ?"
612         hdo=.false. ! default value
613         call getin_p("hdo",hdo)
614         write(*,*) " hdo = ",hdo
615
616         write(*,*) "Use fractionation for hdo?"
617         hdofrac=.true. ! default value
618         call getin_p("hdofrac",hdofrac)
619         write(*,*) " hdofrac = ",hdofrac
620
621! Activeco2ice
622         write(*,*) "Radiatively active transported atmospheric ",
623     &              "Co2 ice ?"
624         activeco2ice=.false. ! default value
625         call getin_p("activeco2ice",activeco2ice)
626         write(*,*) " activeco2ice = ",activeco2ice
627
628! sub-grid cloud fraction: fixed
629         write(*,*) "Fixed cloud fraction?"
630         CLFfixval=1.0 ! default value
631         call getin_p("CLFfixval",CLFfixval)
632         write(*,*) "CLFfixval=",CLFfixval
633! sub-grid cloud fraction: varying
634         write(*,*) "Use partial nebulosity?"
635         CLFvarying=.false. ! default value
636         call getin_p("CLFvarying",CLFvarying)
637         write(*,*)"CLFvarying=",CLFvarying
638
639!CO2 clouds scheme?
640         write(*,*) "Compute CO2 clouds (implies microphysical scheme)?"
641         co2clouds=.false. ! default value
642         call getin_p("co2clouds",co2clouds)
643         write(*,*) " co2clouds = ",co2clouds
644!Can water ice particles serve as CCN for CO2clouds
645         write(*,*) "Use water ice as CO2 clouds CCN ?"
646         co2useh2o=.false. ! default value
647         call getin_p("co2useh2o",co2useh2o)
648         write(*,*) " co2useh2o = ",co2useh2o
649!Do we allow a supply of meteoritic paricles to serve as CO2 ice CCN?
650         write(*,*) "Supply meteoritic particle for CO2 clouds ?"
651         meteo_flux=.false. !Default value
652         call getin_p("meteo_flux",meteo_flux)
653         write(*,*)  " meteo_flux = ",meteo_flux
654!Do we allow a sub-grid temperature distribution for the CO2 microphysics
655         write(*,*) "sub-grid temperature distribution for CO2 clouds?"
656         CLFvaryingCO2=.false. !Default value
657         call getin_p("CLFvaryingCO2",CLFvaryingCO2)
658         write(*,*)  " CLFvaryingCO2 = ",CLFvaryingCO2
659!Amplitude of the sub-grid temperature distribution for the CO2 microphysics
660         write(*,*) "sub-grid temperature amplitude for CO2 clouds?"
661         spantCO2=0 !Default value
662         call getin_p("spantCO2",spantCO2)
663         write(*,*)  " spantCO2 = ",spantCO2
664!Do you want to filter the sub-grid T distribution by a Saturation index?
665         write(*,*) "filter sub-grid temperature by Saturation index?"
666         satindexco2=.true.
667         call getin_p("satindexco2",satindexco2)
668         write(*,*)  " satindexco2 = ",satindexco2
669
670
671! thermal inertia feedback
672         write(*,*) "Activate the thermal inertia feedback ?"
673         tifeedback=.false. ! default value
674         call getin_p("tifeedback",tifeedback)
675         write(*,*) " tifeedback = ",tifeedback
676
677! Test of incompatibility:
678
679         if (tifeedback.and..not.water) then
680           print*,'if tifeedback is used,'
681           print*,'water should be used too'
682           call abort_physic(modname,
683     &          "tifeedback requires water",1)
684         endif
685
686         if (tifeedback.and..not.callsoil) then
687           print*,'if tifeedback is used,'
688           print*,'callsoil should be used too'
689           call abort_physic(modname,
690     &          "tifeedback requires callsoil",1)
691         endif
692
693         if (activice.and..not.water) then
694           print*,'if activice is used, water should be used too'
695           call abort_physic(modname,
696     &          "activeice requires water",1)
697         endif
698
699         if (hdo.and..not.water) then
700           print*,'if hdo is used, water should be used too'
701           call abort_physic(modname,
702     &          "hd2 requires tracer",1)
703         endif
704
705         
706         if (activeco2ice.and..not.co2clouds) then
707          print*,'if activeco2ice is used, co2clouds should be used too'
708          call abort_physic(modname,
709     &          "activeco2ice requires co2clouds",1)
710         endif
711
712! water ice clouds effective variance distribution for sedimentaion       
713        write(*,*) "Sed effective variance for water ice clouds ?"
714        nuice_sed=0.45
715        call getin_p("nuice_sed",nuice_sed)
716        write(*,*) "water_param nueff Sedimentation:", nuice_sed
717             
718        write(*,*) "Sed effective variance for CO2 clouds ?"
719        nuiceco2_sed=0.45
720        call getin_p("nuiceco2_sed",nuiceco2_sed)
721        write(*,*) "CO2 nueff Sedimentation:", nuiceco2_sed
722 
723        write(*,*) "REF effective variance for CO2 clouds ?"
724        nuiceco2_ref=0.45
725        call getin_p("nuiceco2_ref",nuiceco2_ref)
726        write(*,*) "CO2 nueff Sedimentation:", nuiceco2_ref
727
728        write(*,*) "REF effective variance for water clouds ?"
729        nuice_ref=0.1
730        call getin_p("nuice_ref",nuice_ref)
731        write(*,*) "H2O nueff Sedimentation:", nuice_ref
732
733
734! ccn factor if no scavenging         
735        write(*,*) "water param CCN reduc. factor ?"
736        ccn_factor = 4.5
737        call getin_p("ccn_factor",ccn_factor)
738        write(*,*)" ccn_factor = ",ccn_factor
739        write(*,*)"Careful: only used when microphys=F, otherwise"
740        write(*,*)"the contact parameter is used instead;"
741
742       ! microphys
743        write(*,*)"Microphysical scheme for water-ice clouds?"
744        microphys=.false.       ! default value
745        call getin_p("microphys",microphys)
746        write(*,*)" microphys = ",microphys
747
748      ! supersat
749        write(*,*)"Allow super-saturation of water vapor?"
750        supersat=.true.         ! default value
751        call getin_p("supersat",supersat)
752        write(*,*)"supersat = ",supersat
753
754! microphysical parameter contact       
755        write(*,*) "water contact parameter ?"
756        mteta  = 0.95 ! default value
757        temp_dependent_m  = .false. ! default value
758        call getin_p("temp_dependent_m",temp_dependent_m)
759        if (temp_dependent_m) then !(JN 2023)
760           print*,'You have chosen a temperature-dependent water'
761           print*,'contact parameter ! From Maattanen et al. 2014'
762        else if (.not.temp_dependent_m) then
763           print*,'Water contact parameter is constant'
764           call getin_p("mteta",mteta)
765           write(*,*) "mteta = ", mteta
766        endif
767
768! Adaptative timestep for cloud microphysics (JN 2023)
769         write(*,*)"Adaptative timestep for cloud",
770     &              " microphysics ? (default is false)"
771         cloud_adapt_ts=.false. ! default value
772         call getin_p("cloud_adapt_ts",cloud_adapt_ts)
773         write(*,*)"cloud_adapt_ts= ",cloud_adapt_ts
774
775! Test of incompatibility:
776! If you want the adaptative timestep, you should use the
777! temperature dependent contact parameter (otherwise the
778! global water cycle is nuts !)
779! However one can use the temperature dependent contact parameter
780! without the adaptative timestep (MCD6.1 configuration)
781       
782        if (cloud_adapt_ts.and..not.temp_dependent_m) then
783           print*,'Water cycle v6 : if cloud_adapt_ts is used'
784           print*,'then temp_dependent_m must be used!'
785           print*,'Otherwise the water cycle is unrealistic.'
786           call abort_physic(modname,
787     &          "cloud_adapt_ts requires temp_dependent_m",1)
788        endif
789! scavenging
790        write(*,*)"Dust scavenging by H2O/CO2 snowfall ?"
791        scavenging=.false.      ! default value
792        call getin_p("scavenging",scavenging)
793        write(*,*)" scavenging = ",scavenging
794         
795
796! Test of incompatibility:
797! if scavenging is used, then dustbin should be > 0
798
799        if ((microphys.and..not.doubleq).or.
800     &       (microphys.and..not.water)) then
801           print*,'if microphys is used, then doubleq,'
802           print*,'and water must be used!'
803           call abort_physic(modname,
804     &          "microphys requires water and doubleq",1)
805        endif
806        if (microphys.and..not.scavenging) then
807           print*,''
808           print*,'----------------WARNING-----------------'
809           print*,'microphys is used without scavenging !!!'
810           print*,'----------------WARNING-----------------'
811           print*,''
812        endif
813       
814        if ((scavenging.and..not.microphys).or.
815     &       (scavenging.and.(dustbin.lt.1)))then
816           print*,'if scavenging is used, then microphys'
817           print*,'must be used!'
818           call abort_physic(modname,
819     &          "scavenging requires microphys",1)
820        endif
821
822! Instantaneous scavenging by CO2
823! -> expected to be replaced by scavenging with microphysics (flag scavenging) one day
824        write(*,*)"Dust scavenging by instantaneous CO2 snowfall ?"
825        scavco2cond=.false.      ! default value
826        call getin_p("scavco2cond",scavco2cond)
827        write(*,*)" scavco2cond = ",scavco2cond
828! Test of incompatibility:
829! if scavco2cond is used, then dustbin should be > 0
830        if (scavco2cond.and.(dustbin.lt.1))then
831           print*,'if scavco2cond is used, then dustbin should be > 0'
832           call abort_physic(modname,
833     &          "scavco2cond requires dustbin > 0",1)
834        endif
835! if co2clouds is used, then there is no need for scavco2cond
836        if (co2clouds.and.scavco2cond) then
837           print*,''
838           print*,'----------------WARNING-----------------'
839           print*,'     microphys scavenging is used so    '
840           print*,'        no need for scavco2cond !!!     '
841           print*,'----------------WARNING-----------------'
842           print*,''
843           call abort_physic(modname,
844     &          "incompatible co2cloud and scavco2cond options",1)
845        endif
846       
847! Test of incompatibility:
848
849         write(*,*) "Permanent water caps at poles ?",
850     &               " .true. is RECOMMENDED"
851         write(*,*) "(with .true., North cap is a source of water ",
852     &   "and South pole is a cold trap)"
853         caps=.true. ! default value
854         call getin_p("caps",caps)
855         write(*,*) " caps = ",caps
856
857! JN : now separated between albedo_h2o_cap and
858! albedo_h2o_frost. Retrocompatible with old
859! callphys.def with albedo_h2o_ice
860         write(*,*) "water ice albedo ? Old settings use ",
861     &              "albedo_h2o_ice, new settings use ",
862     &              "albedo_h2o_cap and albedo_h2o_frost "
863         albedo_h2o_cap=0.35
864         albedo_h2o_frost=0.35
865         call getin_p("albedo_h2o_ice",albedo_h2o_cap)
866         albedo_h2o_frost=albedo_h2o_cap
867         call getin_p("albedo_h2o_cap",albedo_h2o_cap)
868         write(*,*) " albedo_h2o_cap = ",albedo_h2o_cap
869         call getin_p("albedo_h2o_frost",albedo_h2o_frost)
870         write(*,*) " albedo_h2o_frost = ",albedo_h2o_frost
871
872! Northern polar cap albedo (JN 2021)
873         write(*,*)"Watercaptag albedo is unchanged by water frost",
874     &              " deposition (default is false)"
875         cst_cap_albedo=.false. ! default value
876         call getin_p("cst_cap_albedo",cst_cap_albedo)
877         write(*,*)"cst_cap_albedo = ",cst_cap_albedo
878
879! Watercap evolution & refill (with discriminated albedos) (JN 2021)
880         write(*,*)"Watercap is replenished by water frost",
881     &              " accumulation (default is false)"
882         refill_watercap=.false. ! default value
883         call getin_p("refill_watercap",refill_watercap)
884         write(*,*)"refill_watercap= ",refill_watercap
885! frost thickness threshold for refill_watercap (ice metamorphism)
886         write(*,*) "frost thickness threshold for metamorphism ?",
887     &              "ie converted into watercap",
888     &              "only if refill_watercap is .true."
889         frost_metam_threshold=0.05 !  (i.e 0.05 kg.m-2)
890         call getin_p("frost_metam_threshold",
891     &    frost_metam_threshold)
892         write(*,*) " frost_metam_threshold = ",
893     &            frost_metam_threshold
894
895
896! inert_h2o_ice
897         write(*,*) "water ice thermal inertia ?"
898         inert_h2o_ice=2400 ! (J.m^-2.K^-1.s^-1/2)
899         call getin_p("inert_h2o_ice",inert_h2o_ice)
900         write(*,*) " inert_h2o_ice = ",inert_h2o_ice
901! frost_albedo_threshold
902         write(*,*) "frost thickness threshold for albedo ?"
903         frost_albedo_threshold=0.005 ! 5.4 mic (i.e 0.005 kg.m-2)
904         call getin_p("frost_albedo_threshold",
905     &    frost_albedo_threshold)
906         write(*,*) " frost_albedo_threshold = ",
907     &            frost_albedo_threshold
908
909! TMP: old_wsublimation_scheme
910         write(*,*) "Old water sublimation scheme?"
911         old_wsublimation_scheme = .true.
912         call getin_p("old_wsublimation_scheme",old_wsublimation_scheme)
913         write(*,*) "old_wsublimation_scheme",old_wsublimation_scheme
914
915! call Titus crocus line -- DEFAULT IS NONE
916         write(*,*) "Titus crocus line ?"
917         tituscap=.false.  ! default value
918         call getin_p("tituscap",tituscap)
919         write(*,*) "tituscap",tituscap
920                     
921! Chemistry:
922         write(*,*) "photochemistry: include chemical species"
923         photochem=.false. ! default value
924         call getin_p("photochem",photochem)
925         write(*,*) " photochem = ",photochem
926         
927         write(*,*) "Compute chemistry (if photochem is .true.)",
928     &   "every ichemistry physics step (default: ichemistry=1)"
929         ichemistry=1
930         call getin_p("ichemistry",ichemistry)
931         write(*,*) " ichemistry = ",ichemistry
932
933
934! SCATTERERS
935         write(*,*) "how many scatterers?"
936         naerkind=1 ! default value
937         call getin_p("naerkind",naerkind)
938         write(*,*)" naerkind = ",naerkind
939
940! Test of incompatibility
941c        Logical tests for radiatively active water-ice clouds:
942         IF ( (activice.AND.(.NOT.water)).OR.
943     &        (activice.AND.(naerkind.LT.2)) ) THEN
944           WRITE(*,*) 'If activice is TRUE, water has to be set'
945           WRITE(*,*) 'to TRUE, and "naerkind" must be at least'
946           WRITE(*,*) 'equal to 2.'
947           call abort_physic(modname,
948     &          "radiatively active dust and water"//
949     &          " require naerkind > 1",1)
950         ENDIF
951
952!------------------------------------------
953!------------------------------------------
954! once naerkind is known allocate arrays
955! -- we do it here and not in phys_var_init
956! -- because we need to know naerkind first
957         CALL ini_scatterers(ngrid,nlayer)
958!------------------------------------------
959!------------------------------------------
960
961
962c        Please name the different scatterers here ----------------
963         name_iaer(1) = "dust_conrath"   !! default choice is good old Conrath profile
964         IF (doubleq.AND.active) name_iaer(1) = "dust_doubleq" !! two-moment scheme
965
966         if (nq.gt.1) then
967           ! trick to avoid problems compiling with 1 tracer
968           ! and picky compilers who know name_iaer(2) is out of bounds
969           j=2
970           IF (rdstorm.AND..NOT.activice.AND..NOT.topflows) then
971             name_iaer(j) = "stormdust_doubleq" !! storm dust two-moment scheme
972             j = j+1
973           END IF
974
975           IF (rdstorm.AND.water.AND.activice.AND..NOT.topflows) then
976             name_iaer(j) = "stormdust_doubleq"
977             j = j+1
978           END IF
979
980           IF (topflows.AND..NOT.activice.AND..NOT.rdstorm) then
981             name_iaer(j) = "topdust_doubleq" !! storm dust two-moment scheme
982             j = j+1
983           END IF
984 
985           IF (topflows.AND.water.AND.activice.AND..NOT.rdstorm) then
986             name_iaer(j) =  "topdust_doubleq"
987             j = j+1
988           END IF
989
990           IF (rdstorm.AND.topflows.AND..NOT.activice) THEN
991             name_iaer(j) = "stormdust_doubleq"
992             name_iaer(j+1) = "topdust_doubleq"
993             j = j+2
994           ENDIF
995
996           IF (rdstorm.AND.topflows.AND.water.AND.activice) THEN
997             name_iaer(j) = "stormdust_doubleq"
998             name_iaer(j+1) = "topdust_doubleq"
999             j = j+2
1000           ENDIF
1001
1002           IF (water.AND.activice) then
1003            name_iaer(j) = "h2o_ice"      !! radiatively-active clouds
1004            j = j+1
1005           END IF
1006
1007           IF (co2clouds.AND.activeco2ice) then
1008             name_iaer(j) = "co2_ice" !! radiatively-active co2 clouds
1009             j = j+1
1010           ENDIF
1011
1012           IF (submicron.AND.active) then
1013             name_iaer(j) = "dust_submicron" !! JBM experimental stuff
1014             j = j+1
1015           ENDIF
1016         endif ! of if (nq.gt.1)
1017c        ----------------------------------------------------------
1018
1019! Adsorption
1020         adsorption_soil = .false. ! default value
1021         call getin_p("adsorption_soil",adsorption_soil)
1022         if (adsorption_soil .and. (.not. water)) then
1023              write(*,*)"Adsorption can be run only if water = True"
1024              call abort_physic(modname,
1025     &        "Adsorption must be used with water = true",1)
1026         endif 
1027
1028         choice_ads = 0 ! default value (no adsorption)
1029         if (adsorption_soil) choice_ads = 1
1030         call getin_p("choice_ads",choice_ads)
1031           
1032c        ----------------------------------------------------------
1033
1034! THERMOSPHERE
1035
1036         write(*,*) "call thermosphere ?"
1037         callthermos=.false. ! default value
1038         call getin_p("callthermos",callthermos)
1039         write(*,*) " callthermos = ",callthermos
1040         
1041
1042         write(*,*) " water included without cycle ",
1043     &              "(only if water=.false.)"
1044         thermoswater=.false. ! default value
1045         call getin_p("thermoswater",thermoswater)
1046         write(*,*) " thermoswater = ",thermoswater
1047
1048         write(*,*) "call thermal conduction ?",
1049     &    " (only if callthermos=.true.)"
1050         callconduct=.false. ! default value
1051         call getin_p("callconduct",callconduct)
1052         write(*,*) " callconduct = ",callconduct
1053
1054         write(*,*) "call EUV heating ?",
1055     &   " (only if callthermos=.true.)"
1056         calleuv=.false.  ! default value
1057         call getin_p("calleuv",calleuv)
1058         write(*,*) " calleuv = ",calleuv
1059
1060         write(*,*) "call molecular viscosity ?",
1061     &   " (only if callthermos=.true.)"
1062         callmolvis=.false. ! default value
1063         call getin_p("callmolvis",callmolvis)
1064         write(*,*) " callmolvis = ",callmolvis
1065
1066         write(*,*) "call molecular diffusion ?",
1067     &   " (only if callthermos=.true.)"
1068         callmoldiff=.false. ! default value
1069         call getin_p("callmoldiff",callmoldiff)
1070         write(*,*) " callmoldiff = ",callmoldiff
1071         
1072
1073         write(*,*) "call thermospheric photochemistry ?",
1074     &   " (only if callthermos=.true.)"
1075         thermochem=.false. ! default value
1076         call getin_p("thermochem",thermochem)
1077         write(*,*) " thermochem = ",thermochem
1078
1079         write(*,*) "Method to include solar variability"
1080         write(*,*) "0-> fixed value of E10.7 (fixed_euv_value); ",
1081     &          "1-> daily evolution of E10.7 (for given solvaryear)"
1082         solvarmod=1
1083         call getin_p("solvarmod",solvarmod)
1084         write(*,*) " solvarmod = ",solvarmod
1085
1086         write(*,*) "Fixed euv (for solvarmod==0) 10.7 value?"
1087         write(*,*) " (min=80 , ave=140, max=320)"
1088         fixed_euv_value=140 ! default value
1089         call getin_p("fixed_euv_value",fixed_euv_value)
1090         write(*,*) " fixed_euv_value = ",fixed_euv_value
1091         
1092         write(*,*) "Solar variability as observed for MY: "
1093         write(*,*) "Only if solvarmod=1"
1094         solvaryear=24
1095         call getin_p("solvaryear",solvaryear)
1096         write(*,*) " solvaryear = ",solvaryear
1097
1098         write(*,*) "UV heating efficiency:",
1099     &   "measured values between 0.19 and 0.23 (Fox et al. 1996)",
1100     &   "lower values may be used to compensate low 15 um cooling"
1101         euveff=0.21 !default value
1102         call getin_p("euveff",euveff)
1103         write(*,*) " euveff = ", euveff
1104
1105
1106         if (.not.callthermos) then
1107           if (thermoswater) then
1108             print*,'if thermoswater is set, callthermos must be true'
1109             call abort_physic(modname,
1110     &          "thermoswater requires callthermos",1)
1111           endif         
1112           if (callconduct) then
1113             print*,'if callconduct is set, callthermos must be true'
1114             call abort_physic(modname,
1115     &          "callconduct requires callthermos",1)
1116           endif       
1117           if (calleuv) then
1118             print*,'if calleuv is set, callthermos must be true'
1119             call abort_physic(modname,
1120     &          "calleuv requires callthermos",1)
1121           endif         
1122           if (callmolvis) then
1123             print*,'if callmolvis is set, callthermos must be true'
1124             call abort_physic(modname,
1125     &          "callmolvis requires callthermos",1)
1126           endif       
1127           if (callmoldiff) then
1128             print*,'if callmoldiff is set, callthermos must be true'
1129             call abort_physic(modname,
1130     &          "callmoldiff requires callthermos",1)
1131           endif         
1132           if (thermochem) then
1133             print*,'if thermochem is set, callthermos must be true'
1134             call abort_physic(modname,
1135     &          "thermochem requires callthermos",1)
1136           endif         
1137        endif
1138
1139! Test of incompatibility:
1140! if photochem is used, then water should be used too
1141
1142         if (photochem.and..not.water) then
1143           print*,'if photochem is used, water should be used too'
1144           call abort_physic(modname,
1145     &          "photochem requires water",1)
1146         endif
1147
1148! if callthermos is used, then thermoswater should be used too
1149! (if water not used already)
1150
1151         if (callthermos .and. .not.water) then
1152           if (callthermos .and. .not.thermoswater) then
1153             print*,'if callthermos is used, water or thermoswater
1154     &               should be used too'
1155             call abort_physic(modname,
1156     &          "callthermos requires water or thermoswater",1)
1157           endif
1158         endif
1159
1160         PRINT*,'--------------------------------------------'
1161         PRINT*
1162         PRINT*
1163      ELSE
1164         write(*,*)
1165         write(*,*) 'Cannot read file callphys.def. Is it here ?'
1166         call abort_physic(modname,
1167     &          "missing callphys.def file",1)
1168      ENDIF
1169
11708000  FORMAT(t5,a12,l8)
11718001  FORMAT(t5,a12,i8)
1172
1173      PRINT*
1174      PRINT*,'conf_phys: daysec',daysec
1175      PRINT*
1176      PRINT*,'conf_phys: The radiative transfer is computed:'
1177      PRINT*,'           each ',iradia,' physical time-step'
1178      PRINT*,'        or each ',iradia*dtphys,' seconds'
1179      PRINT*
1180! --------------------------------------------------------------
1181!  Managing the Longwave radiative transfer
1182! --------------------------------------------------------------
1183
1184!     In most cases, the run just use the following values :
1185!     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1186      callemis=.true.     
1187!     ilwd=10*int(daysec/dtphys) ! bug before 22/10/01       
1188      ilwd=1
1189      ilwn=1 !2
1190      ilwb=1 !2
1191      linear=.true.       
1192      ncouche=3
1193      alphan=0.4
1194      semi=0
1195
1196!     BUT people working hard on the LW may want to read them in 'radia.def'
1197!     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1198!$OMP MASTER
1199      OPEN(99,file='radia.def',status='old',form='formatted'
1200     .     ,iostat=ierr)
1201      IF(ierr.EQ.0) THEN
1202         write(*,*) 'conf_phys: Reading radia.def !!!'
1203         READ(99,fmt='(a)') ch1
1204         READ(99,*) callemis
1205         WRITE(*,8000) ch1,callemis
1206
1207         READ(99,fmt='(a)') ch1
1208         READ(99,*) iradia
1209         WRITE(*,8001) ch1,iradia
1210
1211         READ(99,fmt='(a)') ch1
1212         READ(99,*) ilwd
1213         WRITE(*,8001) ch1,ilwd
1214
1215         READ(99,fmt='(a)') ch1
1216         READ(99,*) ilwn
1217         WRITE(*,8001) ch1,ilwn
1218
1219         READ(99,fmt='(a)') ch1
1220         READ(99,*) linear
1221         WRITE(*,8000) ch1,linear
1222
1223         READ(99,fmt='(a)') ch1
1224         READ(99,*) ncouche
1225         WRITE(*,8001) ch1,ncouche
1226
1227         READ(99,fmt='(a)') ch1
1228         READ(99,*) alphan
1229         WRITE(*,*) ch1,alphan
1230
1231         READ(99,fmt='(a)') ch1
1232         READ(99,*) ilwb
1233         WRITE(*,8001) ch1,ilwb
1234
1235
1236         READ(99,fmt='(a)') ch1
1237         READ(99,'(l1)') callg2d
1238         WRITE(*,8000) ch1,callg2d
1239
1240         READ(99,fmt='(a)') ch1
1241         READ(99,*) semi
1242         WRITE(*,*) ch1,semi
1243      end if
1244      CLOSE(99)
1245!$OMP END MASTER
1246      call bcast(ch1)
1247      call bcast(callemis)
1248      call bcast(iradia)
1249      call bcast(ilwd)
1250      call bcast(ilwn)
1251      call bcast(linear)
1252      call bcast(ncouche)
1253      call bcast(alphan)
1254      call bcast(ilwb)
1255      call bcast(callg2d)
1256      call bcast(semi)
1257
1258      END SUBROUTINE conf_phys
1259
1260      END MODULE conf_phys_mod
Note: See TracBrowser for help on using the repository browser.