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

Last change on this file since 1834 was 1832, checked in by mlefevre, 7 years ago

MESOSCALE GENERIC. two things are done in inifis and not necessary in MESOSCALE

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