source: trunk/LMDZ.GENERIC/libf/phystd/inifis_mod.F90 @ 1677

Last change on this file since 1677 was 1677, checked in by sglmd, 8 years ago

Two aerosol kinds added for giant planets: one is a compact (NH3) cloud where the opacity, particle size and bottom pressure level are taken as inputs (a scale height of 0.2 is hard-coded to simulate a compact cloud). Corresponds to option aeronh3. The other one is not generic at all and corresponds to the auroral, stratospheric aerosols observed on Jupiter...(option aeroaurora=.false. by default)

File size: 24.7 KB
Line 
1MODULE inifis_mod
2IMPLICIT NONE
3
4CONTAINS
5
6  SUBROUTINE inifis(ngrid,nlayer,nq, &
7             day_ini,pdaysec,nday,ptimestep, &
8             plat,plon,parea, &
9             prad,pg,pr,pcpp)
10
11  use radinc_h, only: ini_radinc_h, naerkind
12  use radcommon_h, only: ini_radcommon_h
13  use datafile_mod, only: datadir
14  use comdiurn_h, only: sinlat, coslat, sinlon, coslon
15  use comgeomfi_h, only: totarea, totarea_planet
16  use comsoil_h, only: ini_comsoil_h, nsoilmx, lay1_soil, alpha_soil
17  use time_phylmdz_mod, only: ecritphy,day_step,iphysiq, &
18                              init_time, daysec, dtphys
19  use comcstfi_mod, only: rad, cpp, g, r, rcp, &
20                          mugaz, pi, avocado
21  use planete_mod, only: nres
22  use planetwide_mod, only: planetwide_sumval
23  use callkeys_mod
24  use mod_phys_lmdz_para, only : is_parallel
25
26!=======================================================================
27!
28!   purpose:
29!   -------
30!
31!   Initialisation for the physical parametrisations of the LMD
32!   Generic Model.
33!
34!   author: Frederic Hourdin 15 / 10 /93
35!   -------
36!   modified: Sebastien Lebonnois 11/06/2003 (new callphys.def)
37!             Ehouarn Millour (oct. 2008) tracers are now identified
38!              by their names and may not be contiguously
39!              stored in the q(:,:,:,:) array
40!             E.M. (june 2009) use getin routine to load parameters
41!
42!
43!   arguments:
44!   ----------
45!
46!   input:
47!   ------
48!
49!    ngrid                 Size of the horizontal grid.
50!                          All internal loops are performed on that grid.
51!    nlayer                Number of vertical layers.
52!    pdayref               Day of reference for the simulation
53!    pday                  Number of days counted from the North. Spring
54!                          equinoxe.
55!
56!=======================================================================
57!
58!-----------------------------------------------------------------------
59!   declarations:
60!   -------------
61  use datafile_mod, only: datadir
62  use ioipsl_getin_p_mod, only: getin_p
63  IMPLICIT NONE
64
65
66
67  REAL,INTENT(IN) :: prad,pg,pr,pcpp,pdaysec,ptimestep
68  INTEGER,INTENT(IN) :: nday
69  INTEGER,INTENT(IN) :: ngrid,nlayer,nq
70  REAL,INTENT(IN) :: plat(ngrid),plon(ngrid),parea(ngrid)
71  integer,intent(in) :: day_ini
72  INTEGER ig,ierr
73 
74  EXTERNAL iniorbit,orbite
75  EXTERNAL SSUM
76  REAL SSUM
77 
78  ! initialize constants in comcstfi_mod
79  rad=prad
80  cpp=pcpp
81  g=pg
82  r=pr
83  rcp=r/cpp
84  pi=2.*asin(1.)
85  avocado = 6.02214179e23   ! added by RW
86
87  ! Initialize some "temporal and calendar" related variables
88  CALL init_time(day_ini,pdaysec,nday,ptimestep)
89
90  ! read in some parameters from "run.def" for physics,
91  ! or shared between dynamics and physics.
92  call getin_p("ecritphy",ecritphy) ! frequency of outputs in physics,
93                                    ! in dynamical steps
94  call getin_p("day_step",day_step) ! number of dynamical steps per day
95  call getin_p("iphysiq",iphysiq) ! call physics every iphysiq dyn step
96
97  ! do we read a startphy.nc file? (default: .true.)
98  call getin_p("startphy_file",startphy_file)
99 
100! --------------------------------------------------------------
101!  Reading the "callphys.def" file controlling some key options
102! --------------------------------------------------------------
103     
104  ! check that 'callphys.def' file is around
105  OPEN(99,file='callphys.def',status='old',form='formatted',iostat=ierr)
106  CLOSE(99)
107  IF(ierr.EQ.0) iscallphys=.true. !iscallphys initialised as false in callkeys_mod module
108     
109!!!      IF(ierr.EQ.0) THEN
110  IF(iscallphys) THEN
111     PRINT*
112     PRINT*
113     PRINT*,'--------------------------------------------'
114     PRINT*,' inifis: Parametres pour la physique (callphys.def)'
115     PRINT*,'--------------------------------------------'
116
117     write(*,*) "Directory where external input files are:"
118     ! default 'datadir' is set in "datadir_mod"
119     call getin_p("datadir",datadir) ! default path
120     write(*,*) " datadir = ",trim(datadir)
121
122     write(*,*) "Run with or without tracer transport ?"
123     tracer=.false. ! default value
124     call getin_p("tracer",tracer)
125     write(*,*) " tracer = ",tracer
126
127     write(*,*) "Run with or without atm mass update ", &
128            " due to tracer evaporation/condensation?"
129     mass_redistrib=.false. ! default value
130     call getin_p("mass_redistrib",mass_redistrib)
131     write(*,*) " mass_redistrib = ",mass_redistrib
132
133     write(*,*) "Diurnal cycle ?"
134     write(*,*) "(if diurnal=false, diurnal averaged solar heating)"
135     diurnal=.true. ! default value
136     call getin_p("diurnal",diurnal)
137     write(*,*) " diurnal = ",diurnal
138
139     write(*,*) "Seasonal cycle ?"
140     write(*,*) "(if season=false, Ls stays constant, to value ", &
141         "set in 'start'"
142     season=.true. ! default value
143     call getin_p("season",season)
144     write(*,*) " season = ",season
145
146     write(*,*) "Tidally resonant rotation ?"
147     tlocked=.false. ! default value
148     call getin_p("tlocked",tlocked)
149     write(*,*) "tlocked = ",tlocked
150
151     write(*,*) "Saturn ring shadowing ?"
152     rings_shadow = .false.
153     call getin_p("rings_shadow", rings_shadow)
154     write(*,*) "rings_shadow = ", rings_shadow
155         
156     write(*,*) "Compute latitude-dependent gravity field?"
157     oblate = .false.
158     call getin_p("oblate", oblate)
159     write(*,*) "oblate = ", oblate
160
161     write(*,*) "Flattening of the planet (a-b)/a "
162     flatten = 0.0
163     call getin_p("flatten", flatten)
164     write(*,*) "flatten = ", flatten
165         
166
167     write(*,*) "Needed if oblate=.true.: J2"
168     J2 = 0.0
169     call getin_p("J2", J2)
170     write(*,*) "J2 = ", J2
171         
172     write(*,*) "Needed if oblate=.true.: Planet mass (*1e24 kg)"
173     MassPlanet = 0.0
174     call getin_p("MassPlanet", MassPlanet)
175     write(*,*) "MassPlanet = ", MassPlanet         
176
177     write(*,*) "Needed if oblate=.true.: Planet mean radius (m)"
178     Rmean = 0.0
179     call getin_p("Rmean", Rmean)
180     write(*,*) "Rmean = ", Rmean
181         
182! Test of incompatibility:
183! if tlocked, then diurnal should be false
184     if (tlocked.and.diurnal) then
185       print*,'If diurnal=true, we should turn off tlocked.'
186       stop
187     endif
188
189     write(*,*) "Tidal resonance ratio ?"
190     nres=0          ! default value
191     call getin_p("nres",nres)
192     write(*,*) "nres = ",nres
193
194     write(*,*) "Write some extra output to the screen ?"
195     lwrite=.false. ! default value
196     call getin_p("lwrite",lwrite)
197     write(*,*) " lwrite = ",lwrite
198
199     write(*,*) "Save statistics in file stats.nc ?"
200     callstats=.true. ! default value
201     call getin_p("callstats",callstats)
202     write(*,*) " callstats = ",callstats
203
204     write(*,*) "Test energy conservation of model physics ?"
205     enertest=.false. ! default value
206     call getin_p("enertest",enertest)
207     write(*,*) " enertest = ",enertest
208
209     write(*,*) "Check to see if cpp values used match gases.def ?"
210     check_cpp_match=.true. ! default value
211     call getin_p("check_cpp_match",check_cpp_match)
212     write(*,*) " check_cpp_match = ",check_cpp_match
213
214     write(*,*) "call radiative transfer ?"
215     callrad=.true. ! default value
216     call getin_p("callrad",callrad)
217     write(*,*) " callrad = ",callrad
218
219     write(*,*) "call correlated-k radiative transfer ?"
220     corrk=.true. ! default value
221     call getin_p("corrk",corrk)
222     write(*,*) " corrk = ",corrk
223
224     write(*,*) "prohibit calculations outside corrk T grid?"
225     strictboundcorrk=.true. ! default value
226     call getin_p("strictboundcorrk",strictboundcorrk)
227     write(*,*) "strictboundcorrk = ",strictboundcorrk
228
229     write(*,*) "call gaseous absorption in the visible bands?", &
230                    "(matters only if callrad=T)"
231     callgasvis=.false. ! default value
232     call getin_p("callgasvis",callgasvis)
233     write(*,*) " callgasvis = ",callgasvis
234       
235     write(*,*) "call continuum opacities in radiative transfer ?", &
236                    "(matters only if callrad=T)"
237     continuum=.true. ! default value
238     call getin_p("continuum",continuum)
239     write(*,*) " continuum = ",continuum
240
241     write(*,*) "use analytic function for H2O continuum ?"
242     H2Ocont_simple=.false. ! default value
243     call getin_p("H2Ocont_simple",H2Ocont_simple)
244     write(*,*) " H2Ocont_simple = ",H2Ocont_simple
245 
246     write(*,*) "call turbulent vertical diffusion ?"
247     calldifv=.true. ! default value
248     call getin_p("calldifv",calldifv)
249     write(*,*) " calldifv = ",calldifv
250
251     write(*,*) "use turbdiff instead of vdifc ?"
252     UseTurbDiff=.true. ! default value
253     call getin_p("UseTurbDiff",UseTurbDiff)
254     write(*,*) " UseTurbDiff = ",UseTurbDiff
255
256     write(*,*) "call convective adjustment ?"
257     calladj=.true. ! default value
258     call getin_p("calladj",calladj)
259     write(*,*) " calladj = ",calladj
260
261     write(*,*) "call CO2 condensation ?"
262     co2cond=.false. ! default value
263     call getin_p("co2cond",co2cond)
264     write(*,*) " co2cond = ",co2cond
265! Test of incompatibility
266     if (co2cond.and.(.not.tracer)) then
267        print*,'We need a CO2 ice tracer to condense CO2'
268        call abort
269     endif
270 
271     write(*,*) "CO2 supersaturation level ?"
272     co2supsat=1.0 ! default value
273     call getin_p("co2supsat",co2supsat)
274     write(*,*) " co2supsat = ",co2supsat
275
276     write(*,*) "Radiative timescale for Newtonian cooling ?"
277     tau_relax=30. ! default value
278     call getin_p("tau_relax",tau_relax)
279     write(*,*) " tau_relax = ",tau_relax
280     tau_relax=tau_relax*24*3600 ! convert Earth days --> seconds
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     write(*,*)"Rad transfer is computed every iradia", &
288                   " physical timestep"
289     iradia=1 ! default value
290     call getin_p("iradia",iradia)
291     write(*,*)" iradia = ",iradia
292       
293     write(*,*)"Rayleigh scattering ?"
294     rayleigh=.false.
295     call getin_p("rayleigh",rayleigh)
296     write(*,*)" rayleigh = ",rayleigh
297
298     write(*,*) "Use blackbody for stellar spectrum ?"
299     stelbbody=.false. ! default value
300     call getin_p("stelbbody",stelbbody)
301     write(*,*) " stelbbody = ",stelbbody
302
303     write(*,*) "Stellar blackbody temperature ?"
304     stelTbb=5800.0 ! default value
305     call getin_p("stelTbb",stelTbb)
306     write(*,*) " stelTbb = ",stelTbb
307
308     write(*,*)"Output mean OLR in 1D?"
309     meanOLR=.false.
310     call getin_p("meanOLR",meanOLR)
311     write(*,*)" meanOLR = ",meanOLR
312
313     write(*,*)"Output spectral OLR in 3D?"
314     specOLR=.false.
315     call getin_p("specOLR",specOLR)
316     write(*,*)" specOLR = ",specOLR
317
318     write(*,*)"Operate in kastprof mode?"
319     kastprof=.false.
320     call getin_p("kastprof",kastprof)
321     write(*,*)" kastprof = ",kastprof
322
323     write(*,*)"Uniform absorption in radiative transfer?"
324     graybody=.false.
325     call getin_p("graybody",graybody)
326     write(*,*)" graybody = ",graybody
327
328! Soil model
329     write(*,*)"Number of sub-surface layers for soil scheme?"
330     ! default value of nsoilmx set in comsoil_h
331     call getin_p("nsoilmx",nsoilmx)
332     write(*,*)" nsoilmx=",nsoilmx
333     
334     write(*,*)"Thickness of topmost soil layer (m)?"
335     ! default value of lay1_soil set in comsoil_h
336     call getin_p("lay1_soil",lay1_soil)
337     write(*,*)" lay1_soil = ",lay1_soil
338     
339     write(*,*)"Coefficient for soil layer thickness distribution?"
340     ! default value of alpha_soil set in comsoil_h
341     call getin_p("alpha_soil",alpha_soil)
342     write(*,*)" alpha_soil = ",alpha_soil
343
344! Slab Ocean
345     write(*,*) "Use slab-ocean ?"
346     ok_slab_ocean=.false.         ! default value
347     call getin_p("ok_slab_ocean",ok_slab_ocean)
348     write(*,*) "ok_slab_ocean = ",ok_slab_ocean
349     ! Sanity check: for now slab oncean only works in serial mode
350     if (ok_slab_ocean.and.is_parallel) then
351       write(*,*) " Error: slab ocean should only be used in serial mode!"
352       call abort
353     endif
354
355     write(*,*) "Use slab-sea-ice ?"
356     ok_slab_sic=.true.         ! default value
357     call getin_p("ok_slab_sic",ok_slab_sic)
358     write(*,*) "ok_slab_sic = ",ok_slab_sic
359
360     write(*,*) "Use heat transport for the ocean ?"
361     ok_slab_heat_transp=.true.   ! default value
362     call getin_p("ok_slab_heat_transp",ok_slab_heat_transp)
363     write(*,*) "ok_slab_heat_transp = ",ok_slab_heat_transp
364
365
366
367! Test of incompatibility:
368! if kastprof used, we must be in 1D
369     if (kastprof.and.(ngrid.gt.1)) then
370       print*,'kastprof can only be used in 1D!'
371       call abort
372     endif
373
374     write(*,*)"Stratospheric temperature for kastprof mode?"
375     Tstrat=167.0
376     call getin_p("Tstrat",Tstrat)
377     write(*,*)" Tstrat = ",Tstrat
378
379     write(*,*)"Remove lower boundary?"
380     nosurf=.false.
381     call getin_p("nosurf",nosurf)
382     write(*,*)" nosurf = ",nosurf
383
384! Tests of incompatibility:
385     if (nosurf.and.callsoil) then
386       print*,'nosurf not compatible with soil scheme!'
387       print*,'... got to make a choice!'
388       call abort
389     endif
390
391     write(*,*)"Add an internal heat flux?", &
392                   "... matters only if callsoil=F"
393     intheat=0.
394     call getin_p("intheat",intheat)
395     write(*,*)" intheat = ",intheat
396
397     write(*,*)"Use Newtonian cooling for radiative transfer?"
398     newtonian=.false.
399     call getin_p("newtonian",newtonian)
400     write(*,*)" newtonian = ",newtonian
401
402! Tests of incompatibility:
403     if (newtonian.and.corrk) then
404       print*,'newtonian not compatible with correlated-k!'
405       call abort
406     endif
407     if (newtonian.and.calladj) then
408       print*,'newtonian not compatible with adjustment!'
409       call abort
410     endif
411     if (newtonian.and.calldifv) then
412       print*,'newtonian not compatible with a boundary layer!'
413       call abort
414     endif
415
416     write(*,*)"Test physics timescale in 1D?"
417     testradtimes=.false.
418     call getin_p("testradtimes",testradtimes)
419     write(*,*)" testradtimes = ",testradtimes
420
421! Test of incompatibility:
422! if testradtimes used, we must be in 1D
423     if (testradtimes.and.(ngrid.gt.1)) then
424       print*,'testradtimes can only be used in 1D!'
425       call abort
426     endif
427
428     write(*,*)"Default planetary temperature?"
429     tplanet=215.0
430     call getin_p("tplanet",tplanet)
431     write(*,*)" tplanet = ",tplanet
432
433     write(*,*)"Which star?"
434     startype=1 ! default value = Sol
435     call getin_p("startype",startype)
436     write(*,*)" startype = ",startype
437
438     write(*,*)"Value of stellar flux at 1 AU?"
439     Fat1AU=1356.0 ! default value = Sol today
440     call getin_p("Fat1AU",Fat1AU)
441     write(*,*)" Fat1AU = ",Fat1AU
442
443
444! TRACERS:
445
446     write(*,*)"Varying H2O cloud fraction?"
447     CLFvarying=.false.     ! default value
448     call getin_p("CLFvarying",CLFvarying)
449     write(*,*)" CLFvarying = ",CLFvarying
450
451     write(*,*)"Value of fixed H2O cloud fraction?"
452     CLFfixval=1.0                ! default value
453     call getin_p("CLFfixval",CLFfixval)
454     write(*,*)" CLFfixval = ",CLFfixval
455
456     write(*,*)"fixed radii for Cloud particles?"
457     radfixed=.false. ! default value
458     call getin_p("radfixed",radfixed)
459     write(*,*)" radfixed = ",radfixed
460
461     if(kastprof)then
462        radfixed=.true.
463     endif 
464
465     write(*,*)"Number mixing ratio of CO2 ice particles:"
466     Nmix_co2=1.e6 ! default value
467     call getin_p("Nmix_co2",Nmix_co2)
468     write(*,*)" Nmix_co2 = ",Nmix_co2
469
470!         write(*,*)"Number of radiatively active aerosols:"
471!         naerkind=0. ! default value
472!         call getin_p("naerkind",naerkind)
473!         write(*,*)" naerkind = ",naerkind
474
475     write(*,*)"Opacity of dust (if used):"
476     dusttau=0. ! default value
477     call getin_p("dusttau",dusttau)
478     write(*,*)" dusttau = ",dusttau
479
480     write(*,*)"Radiatively active CO2 aerosols?"
481     aeroco2=.false.     ! default value
482     call getin_p("aeroco2",aeroco2)
483     write(*,*)" aeroco2 = ",aeroco2
484
485     write(*,*)"Fixed CO2 aerosol distribution?"
486     aerofixco2=.false.     ! default value
487     call getin_p("aerofixco2",aerofixco2)
488     write(*,*)" aerofixco2 = ",aerofixco2
489
490     write(*,*)"Radiatively active water ice?"
491     aeroh2o=.false.     ! default value
492     call getin_p("aeroh2o",aeroh2o)
493     write(*,*)" aeroh2o = ",aeroh2o
494
495     write(*,*)"Fixed H2O aerosol distribution?"
496     aerofixh2o=.false.     ! default value
497     call getin_p("aerofixh2o",aerofixh2o)
498     write(*,*)" aerofixh2o = ",aerofixh2o
499
500     write(*,*)"Radiatively active sulfuric acid aerosols?"
501     aeroh2so4=.false.     ! default value
502     call getin_p("aeroh2so4",aeroh2so4)
503     write(*,*)" aeroh2so4 = ",aeroh2so4
504         
505!=================================
506
507     write(*,*)"Radiatively active two-layer aerosols?"
508     aeroback2lay=.false.     ! default value
509     call getin_p("aeroback2lay",aeroback2lay)
510     write(*,*)" aeroback2lay = ",aeroback2lay
511
512     write(*,*)"Radiatively active ammonia cloud?"
513     aeronh3=.false.     ! default value
514     call getin_p("aeronh3",aeronh3)
515     write(*,*)" aeronh3 = ",aeronh3
516
517     write(*,*)"Radiatively active auroral aerosols?"
518     aeroaurora=.false.     ! default value
519     call getin_p("aeroaurora",aeroaurora)
520     write(*,*)" aeroaurora = ",aeroaurora
521
522     write(*,*)"TWOLAY AEROSOL: total optical depth ", &
523                    "in the tropospheric layer (visible)"
524     obs_tau_col_tropo=8.D0
525     call getin_p("obs_tau_col_tropo",obs_tau_col_tropo)
526     write(*,*)" obs_tau_col_tropo = ",obs_tau_col_tropo
527
528     write(*,*)"TWOLAY AEROSOL: total optical depth ", &
529                    "in the stratospheric layer (visible)"
530     obs_tau_col_strato=0.08D0
531     call getin_p("obs_tau_col_strato",obs_tau_col_strato)
532     write(*,*)" obs_tau_col_strato = ",obs_tau_col_strato
533
534     write(*,*)"TWOLAY AEROSOL: pres_bottom_tropo? in pa"
535     pres_bottom_tropo=66000.0
536     call getin_p("pres_bottom_tropo",pres_bottom_tropo)
537     write(*,*)" pres_bottom_tropo = ",pres_bottom_tropo
538
539     write(*,*)"TWOLAY AEROSOL: pres_top_tropo? in pa"
540     pres_top_tropo=18000.0
541     call getin_p("pres_top_tropo",pres_top_tropo)
542     write(*,*)" pres_top_tropo = ",pres_top_tropo
543
544     write(*,*)"TWOLAY AEROSOL: pres_bottom_strato? in pa"
545     pres_bottom_strato=2000.0
546     call getin_p("pres_bottom_strato",pres_bottom_strato)
547     write(*,*)" pres_bottom_strato = ",pres_bottom_strato
548
549     write(*,*)"TWOLAY AEROSOL: pres_top_strato? in pa"
550     pres_top_strato=100.0
551     call getin_p("pres_top_strato",pres_top_strato)
552     write(*,*)" pres_top_strato = ",pres_top_strato
553
554     write(*,*)"TWOLAY AEROSOL: particle size in the ", &
555                    "tropospheric layer, in meters"
556     size_tropo=2.e-6
557     call getin_p("size_tropo",size_tropo)
558     write(*,*)" size_tropo = ",size_tropo
559
560     write(*,*)"TWOLAY AEROSOL: particle size in the ", &
561                    "stratospheric layer, in meters"
562     size_strato=1.e-7
563     call getin_p("size_strato",size_strato)
564     write(*,*)" size_strato = ",size_strato
565
566     write(*,*)"NH3 (thin) cloud: total optical depth"
567     tau_nh3_cloud=7.D0
568     call getin_p("tau_nh3_cloud",tau_nh3_cloud)
569     write(*,*)" tau_nh3_cloud = ",tau_nh3_cloud
570
571     write(*,*)"NH3 (thin) cloud pressure level"
572     pres_nh3_cloud=7.D0
573     call getin_p("pres_nh3_cloud",pres_nh3_cloud)
574     write(*,*)" pres_nh3_cloud = ",pres_nh3_cloud
575
576     write(*,*)"NH3 (thin) cloud: particle sizes"
577     size_nh3_cloud=3.e-6
578     call getin_p("size_nh3_cloud",size_nh3_cloud)
579     write(*,*)" size_nh3_cloud = ",size_nh3_cloud
580
581!=================================
582
583     write(*,*)"Cloud pressure level (with kastprof only):"
584     cloudlvl=0. ! default value
585     call getin_p("cloudlvl",cloudlvl)
586     write(*,*)" cloudlvl = ",cloudlvl
587
588     write(*,*)"Is the variable gas species radiatively active?"
589     Tstrat=167.0
590     varactive=.false.
591     call getin_p("varactive",varactive)
592     write(*,*)" varactive = ",varactive
593
594     write(*,*)"Is the variable gas species distribution set?"
595     varfixed=.false.
596     call getin_p("varfixed",varfixed)
597     write(*,*)" varfixed = ",varfixed
598
599     write(*,*)"What is the saturation % of the variable species?"
600     satval=0.8
601     call getin_p("satval",satval)
602     write(*,*)" satval = ",satval
603
604
605! Test of incompatibility:
606! if varactive, then varfixed should be false
607     if (varactive.and.varfixed) then
608       print*,'if varactive, varfixed must be OFF!'
609       stop
610     endif
611
612     write(*,*) "Gravitationnal sedimentation ?"
613     sedimentation=.false. ! default value
614     call getin_p("sedimentation",sedimentation)
615     write(*,*) " sedimentation = ",sedimentation
616
617     write(*,*) "Compute water cycle ?"
618     water=.false. ! default value
619     call getin_p("water",water)
620     write(*,*) " water = ",water
621         
622! Test of incompatibility:
623! if water is true, there should be at least a tracer
624     if (water.and.(.not.tracer)) then
625        print*,'if water is ON, tracer must be ON too!'
626        stop
627     endif
628
629     write(*,*) "Include water condensation ?"
630     watercond=.false. ! default value
631     call getin_p("watercond",watercond)
632     write(*,*) " watercond = ",watercond
633
634! Test of incompatibility:
635! if watercond is used, then water should be used too
636     if (watercond.and.(.not.water)) then
637        print*,'if watercond is used, water should be used too'
638        stop
639     endif
640
641     write(*,*) "Include water precipitation ?"
642     waterrain=.false. ! default value
643     call getin_p("waterrain",waterrain)
644     write(*,*) " waterrain = ",waterrain
645
646     write(*,*) "Include surface hydrology ?"
647     hydrology=.false. ! default value
648     call getin_p("hydrology",hydrology)
649     write(*,*) " hydrology = ",hydrology
650
651     write(*,*) "Evolve surface water sources ?"
652     sourceevol=.false. ! default value
653     call getin_p("sourceevol",sourceevol)
654     write(*,*) " sourceevol = ",sourceevol
655
656     write(*,*) "Ice evolution timestep ?"
657     icetstep=100.0 ! default value
658     call getin_p("icetstep",icetstep)
659     write(*,*) " icetstep = ",icetstep
660         
661     write(*,*) "Spectral Dependant albedo ?"
662     albedo_spectral_mode=.false. ! default value
663     call getin_p("albedo_spectral_mode",albedo_spectral_mode)
664     write(*,*) " albedo_spectral_mode = ",albedo_spectral_mode
665
666     write(*,*) "Snow albedo ?"
667     write(*,*) "If albedo_spectral_mode=.true., then this "
668     write(*,*) "corresponds to the 0.5 microns snow albedo."
669     albedosnow=0.5         ! default value
670     call getin_p("albedosnow",albedosnow)
671     write(*,*) " albedosnow = ",albedosnow
672         
673     write(*,*) "CO2 ice albedo ?"
674     albedoco2ice=0.5       ! default value
675     call getin_p("albedoco2ice",albedoco2ice)
676     write(*,*) " albedoco2ice = ",albedoco2ice
677
678     write(*,*) "Maximum ice thickness ?"
679     maxicethick=2.0         ! default value
680     call getin_p("maxicethick",maxicethick)
681     write(*,*) " maxicethick = ",maxicethick
682
683     write(*,*) "Freezing point of seawater ?"
684     Tsaldiff=-1.8          ! default value
685     call getin_p("Tsaldiff",Tsaldiff)
686     write(*,*) " Tsaldiff = ",Tsaldiff
687
688     write(*,*) "Does user want to force cpp and mugaz?"
689     force_cpp=.false. ! default value
690     call getin_p("force_cpp",force_cpp)
691     write(*,*) " force_cpp = ",force_cpp
692
693     if (force_cpp) then
694       mugaz = -99999.
695       PRINT *,'MEAN MOLECULAR MASS in g mol-1 ?'
696       call getin_p("mugaz",mugaz)
697       IF (mugaz.eq.-99999.) THEN
698           PRINT *, "mugaz must be set if force_cpp = T"
699           STOP
700       ELSE
701           write(*,*) "mugaz=",mugaz
702       ENDIF
703       cpp = -99999.
704       PRINT *,'SPECIFIC HEAT CAPACITY in J K-1 kg-1 ?'
705       call getin_p("cpp",cpp)
706       IF (cpp.eq.-99999.) THEN
707           PRINT *, "cpp must be set if force_cpp = T"
708           STOP
709       ELSE
710           write(*,*) "cpp=",cpp
711       ENDIF
712!         else
713!           mugaz=8.314*1000./pr
714     endif ! of if (force_cpp)
715     call su_gases
716     call calc_cpp_mugaz
717
718     PRINT*,'--------------------------------------------'
719     PRINT*
720     PRINT*
721  ELSE
722     write(*,*)
723     write(*,*) 'Cannot read file callphys.def. Is it here ?'
724     stop
725  ENDIF ! of IF(iscallphys)
726
727  PRINT*
728  PRINT*,'inifis: daysec',daysec
729  PRINT*
730  PRINT*,'inifis: The radiative transfer is computed:'
731  PRINT*,'           each ',iradia,' physical time-step'
732  PRINT*,'        or each ',iradia*dtphys,' seconds'
733  PRINT*
734
735
736!-----------------------------------------------------------------------
737!     Some more initialization:
738!     ------------------------
739
740  ! Initializations for comgeomfi_h
741  totarea=SSUM(ngrid,parea,1)
742  call planetwide_sumval(parea,totarea_planet)
743
744  !! those are defined in comdiurn_h.F90
745  IF (.not.ALLOCATED(sinlat)) ALLOCATE(sinlat(ngrid))
746  IF (.not.ALLOCATED(coslat)) ALLOCATE(coslat(ngrid))
747  IF (.not.ALLOCATED(sinlon)) ALLOCATE(sinlon(ngrid))
748  IF (.not.ALLOCATED(coslon)) ALLOCATE(coslon(ngrid))
749
750  DO ig=1,ngrid
751     sinlat(ig)=sin(plat(ig))
752     coslat(ig)=cos(plat(ig))
753     sinlon(ig)=sin(plon(ig))
754     coslon(ig)=cos(plon(ig))
755  ENDDO
756
757  ! initialize variables in radinc_h
758  call ini_radinc_h(nlayer)
759 
760  ! allocate "radcommon_h" arrays
761  call ini_radcommon_h()
762
763  ! allocate "comsoil_h" arrays
764  call ini_comsoil_h(ngrid)
765     
766  END SUBROUTINE inifis
767
768END MODULE inifis_mod
Note: See TracBrowser for help on using the repository browser.