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

Last change on this file since 3225 was 3167, checked in by llange, 14 months ago

Mars PCM
Introducing the scheme from ATKE workshop to solve turbulent diffusion + surface layer parameterization.
Works only if callatke = .true. in the callphys.def. By default, it is false and the model runs as usual with the yamada 2.5 closure
Tuning of the several parameters for the ATKE in progress
LL

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