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

Last change on this file since 1715 was 1715, checked in by jvatant, 7 years ago

Cleaning of the radiative code + coherence between optci and optcv :

+ Get rid of the actually dummy and confusing extra level L_LEVELS+1 for aerosols
+ Harmonisation between optci and optcv
+ Get rid of tauref (called nowhere) and csqtly of ini_radcommon subroutine

JVO

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