source: trunk/LMDZ.TITAN/libf/phytitan/inifis_mod.F90 @ 1644

Last change on this file since 1644 was 1542, checked in by emillour, 9 years ago

Generic GCM:

  • fix for 1D in writediagfi to enable writing at "ecritphy" rate.
  • move iniprint.h to "misc"
  • Some code cleanup in anticipation of future updates:
    • changed variable names in comgeomphy.F90: give them more explicit names: rlond => longitude , rlatd => latitude, airephy => cell_area, cuphy => dx , cvphy => dy
    • removed long(), lati() and area() from comgeomfi_h.F90, use longitude(), latitude() and cell_are() from comgeomphy.F90 instead

EM

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