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

Last change on this file since 3083 was 3083, checked in by slebonnois, 14 months ago

BBT : Update for the titan microphysics and cloud model

File size: 21.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
13  use comdiurn_h, only: sinlat, coslat, sinlon, coslon
14  use comgeomfi_h, only: totarea, totarea_planet
15  use comsoil_h, only: ini_comsoil_h, nsoilmx, lay1_soil, alpha_soil
16  use time_phylmdz_mod, only: ecritphy,day_step,iphysiq, &
17                              init_time, daysec, dtphys
18  use comcstfi_mod, only: rad, cpp, g, r, rcp, &
19                          mugaz, pi, avocado, kbol
20  use planete_mod, only: nres
21  use planetwide_mod, only: planetwide_sumval
22  use callkeys_mod
23  use mod_phys_lmdz_para, only : is_parallel
24
25!=======================================================================
26!
27!   purpose:
28!   -------
29!
30!   Initialisation for the physical parametrisations of the LMD
31!   Generic Model.
32!
33!   author: Frederic Hourdin 15 / 10 /93
34!   -------
35!   modified: Sebastien Lebonnois 11/06/2003 (new callphys.def)
36!             Ehouarn Millour (oct. 2008) tracers are now identified
37!              by their names and may not be contiguously
38!              stored in the q(:,:,:,:) array
39!             E.M. (june 2009) use getin routine to load parameters
40!
41!
42!   arguments:
43!   ----------
44!
45!   input:
46!   ------
47!
48!    ngrid                 Size of the horizontal grid.
49!                          All internal loops are performed on that grid.
50!    nlayer                Number of vertical layers.
51!    pdayref               Day of reference for the simulation
52!    pday                  Number of days counted from the North. Spring
53!                          equinoxe.
54!
55!=======================================================================
56!
57!-----------------------------------------------------------------------
58!   declarations:
59!   -------------
60  use datafile_mod
61  use ioipsl_getin_p_mod, only: getin_p
62  IMPLICIT NONE
63
64
65
66  REAL,INTENT(IN) :: prad,pg,pr,pcpp,pdaysec,ptimestep
67  INTEGER,INTENT(IN) :: nday
68  INTEGER,INTENT(IN) :: ngrid,nlayer,nq
69  REAL,INTENT(IN) :: plat(ngrid),plon(ngrid),parea(ngrid)
70  integer,intent(in) :: day_ini
71  INTEGER ig,ierr
72 
73  EXTERNAL iniorbit,orbite
74  EXTERNAL SSUM
75  REAL SSUM
76 
77  ! Initialize flags lunout, prt_level, debug (in print_control_mod)
78  CALL init_print_control
79
80  ! initialize constants in comcstfi_mod
81  rad=prad
82  cpp=pcpp
83  g=pg
84  r=pr
85  rcp=r/cpp
86  mugaz=8.314*1000./pr ! dummy init
87  pi=2.*asin(1.)
88  avocado = 6.02214179e23   ! added by RW
89  kbol = 1.38064852e-23  ! added by JVO for Titan chem
90
91  ! Initialize some "temporal and calendar" related variables
92#ifndef MESOSCALE
93  CALL init_time(day_ini,pdaysec,nday,ptimestep)
94#endif
95
96  ! read in some parameters from "run.def" for physics,
97  ! or shared between dynamics and physics.
98  call getin_p("ecritphy",ecritphy) ! frequency of outputs in physics,
99                                    ! in dynamical steps
100  call getin_p("day_step",day_step) ! number of dynamical steps per day
101  call getin_p("iphysiq",iphysiq) ! call physics every iphysiq dyn step
102
103  ! do we read a startphy.nc file? (default: .true.)
104  call getin_p("startphy_file",startphy_file)
105 
106! --------------------------------------------------------------
107!  Reading the "callphys.def" file controlling some key options
108! --------------------------------------------------------------
109     
110  ! check that 'callphys.def' file is around
111  OPEN(99,file='callphys.def',status='old',form='formatted',iostat=ierr)
112  CLOSE(99)
113  IF(ierr.EQ.0) iscallphys=.true. !iscallphys initialised as false in callkeys_mod module
114     
115!!!      IF(ierr.EQ.0) THEN
116  IF(iscallphys) THEN
117     PRINT*
118     PRINT*
119     PRINT*,'--------------------------------------------'
120     PRINT*,' inifis: Parametres pour la physique (callphys.def)'
121     PRINT*,'--------------------------------------------'
122
123     write(*,*) "Directory where external input files are:"
124     ! default 'datadir' is set in "datadir_mod"
125     call getin_p("datadir",datadir) ! default path
126     write(*,*) " datadir = ",trim(datadir)
127
128     write(*,*) "Run with or without tracer transport ?"
129     tracer=.false. ! default value
130     call getin_p("tracer",tracer)
131     write(*,*) " tracer = ",tracer
132
133     write(*,*) "Run with or without atm mass update ", &
134            " due to tracer evaporation/condensation?"
135     mass_redistrib=.false. ! default value
136     call getin_p("mass_redistrib",mass_redistrib)
137     write(*,*) " mass_redistrib = ",mass_redistrib
138
139     write(*,*) "Diurnal cycle ?"
140     write(*,*) "(if diurnal=false, diurnal averaged solar heating)"
141     diurnal=.true. ! default value
142     call getin_p("diurnal",diurnal)
143     write(*,*) " diurnal = ",diurnal
144
145     write(*,*) "Seasonal cycle ?"
146     write(*,*) "(if season=false, Ls stays constant, to value ", &
147         "set in 'start'"
148     season=.true. ! default value
149     call getin_p("season",season)
150     write(*,*) " season = ",season
151     
152     write(*,*) "No seasonal cycle: initial day to lock the run during restart"
153     noseason_day=0.0 ! default value
154     call getin_p("noseason_day",noseason_day)
155     write(*,*) "noseason_day=", noseason_day
156
157     write(*,*) "Tidally resonant rotation ?"
158     tlocked=.false. ! default value
159     call getin_p("tlocked",tlocked)
160     write(*,*) "tlocked = ",tlocked
161
162     write(*,*) "Saturn ring shadowing ?"
163     rings_shadow = .false.
164     call getin_p("rings_shadow", rings_shadow)
165     write(*,*) "rings_shadow = ", rings_shadow
166         
167     write(*,*) "Compute latitude-dependent gravity field?"
168     oblate = .false.
169     call getin_p("oblate", oblate)
170     write(*,*) "oblate = ", oblate
171
172     write(*,*) "Flattening of the planet (a-b)/a "
173     flatten = 0.0
174     call getin_p("flatten", flatten)
175     write(*,*) "flatten = ", flatten         
176
177     write(*,*) "Needed if oblate=.true.: J2"
178     J2 = 0.0
179     call getin_p("J2", J2)
180     write(*,*) "J2 = ", J2
181         
182     write(*,*) "Needed if oblate=.true.: Planet mass (*1e24 kg)"
183     MassPlanet = 0.0
184     call getin_p("MassPlanet", MassPlanet)
185     write(*,*) "MassPlanet = ", MassPlanet         
186
187     write(*,*) "Needed if oblate=.true.: Planet mean radius (m)"
188     Rmean = 0.0
189     call getin_p("Rmean", Rmean)
190     write(*,*) "Rmean = ", Rmean
191     
192     write(*,*) "Compute effective altitude-dependent gravity field?"
193     eff_gz = .false.
194     call getin_p("eff_gz", eff_gz)
195     write(*,*) "eff_gz = ", eff_gz
196
197     write(*,*) "Nudging of zonal wind to keep the super-rotation"
198     nudging_u = .true.
199     call getin_p("nudging_u", nudging_u)
200     write(*,*) "nudging_u = ", nudging_u
201
202     write(*,*) "Nudging relaxation time (here ~ 1 titanian year in secondes)"
203     nudging_dt = 9.3e8
204     call getin_p("nudging_dt", nudging_dt)
205     write(*,*) "nudging_dt = ", nudging_dt
206
207     write(*,*) "New optics for clouds"
208     opt4clouds = .true.
209     call getin_p("opt4clouds", opt4clouds)
210     write(*,*) "opt4clouds = ", opt4clouds
211
212     write(*,*) "Cloudy fraction in the Clear / Dark column method"
213     Fcloudy = 1.0
214     call getin_p("Fcloudy", Fcloudy)
215     write(*,*) "Fcloudy = ", Fcloudy
216
217     write(*,*) "Adjustment of single scattering albedo for cloudy dropplet"
218     Fssa = 1.0
219     call getin_p("Fssa", Fssa)
220     write(*,*) "Fssa = ", Fssa
221     
222     write(*,*) "Adjustment of aerosol properties in the VIS"
223     FHVIS = 1.0
224     call getin_p("FHVIS", FHVIS)
225     write(*,*) "FHVIS = ", FHVIS
226
227     write(*,*) "Adjustment of aerosol properties in the IR"
228     FHIR = 1.0
229     call getin_p("FHIR", FHIR)
230     write(*,*) "FHIR = ", FHIR
231
232     write(*,*) "Infinite tank of CH4 ?"
233     resCH4_inf = .false.
234     call getin_p("resCH4_inf", resCH4_inf)
235     write(*,*) "resCH4_inf = ", resCH4_inf
236     
237     ! sanity check warning
238     if (eff_gz) then
239       print*,"WARNING : You run chemistry with effective altitude-dependent gravity field !!"
240       print*,"You will have no coherence in your heating rates between physics and dynamics !!"
241       print*,"I let you continue but you should rather set eff_gz =.false. ..."
242     endif
243
244         
245! Test of incompatibility:
246! if tlocked, then diurnal should be false
247     if (tlocked.and.diurnal) then
248       print*,'If diurnal=true, we should turn off tlocked.'
249       stop
250     endif
251
252     write(*,*) "Tidal resonance ratio ?"
253     nres=0          ! default value
254     call getin_p("nres",nres)
255     write(*,*) "nres = ",nres
256
257     write(*,*) "Write some extra output to the screen ?"
258     lwrite=.false. ! default value
259     call getin_p("lwrite",lwrite)
260     write(*,*) " lwrite = ",lwrite
261
262     write(*,*) "Save statistics in file stats.nc ?"
263     callstats=.true. ! default value
264     call getin_p("callstats",callstats)
265     write(*,*) " callstats = ",callstats
266
267     write(*,*) "Test energy conservation of model physics ?"
268     enertest=.false. ! default value
269     call getin_p("enertest",enertest)
270     write(*,*) " enertest = ",enertest
271
272     write(*,*) "Check to see if cpp values used match gases.def ?"
273     check_cpp_match=.true. ! default value
274     call getin_p("check_cpp_match",check_cpp_match)
275     write(*,*) " check_cpp_match = ",check_cpp_match
276
277     write(*,*) "call radiative transfer ?"
278     callrad=.true. ! default value
279     call getin_p("callrad",callrad)
280     write(*,*) " callrad = ",callrad
281
282     write(*,*) "call correlated-k radiative transfer ?"
283     corrk=.true. ! default value
284     call getin_p("corrk",corrk)
285     write(*,*) " corrk = ",corrk
286     
287     if (corrk) then
288       ! default path is set in datadir
289       write(*,*) "callcorrk: Correlated-k data base folder:",trim(datadir)
290       call getin_p("corrkdir",corrkdir)
291       write(*,*) " corrkdir = ",corrkdir
292       
293       write(*,*) "use correlated-k recombination instead of pre-mixed values ?"
294       corrk_recombin=.false.! default value
295       call getin_p("corrk_recombin",corrk_recombin)
296       write(*,*) " corrk_recombin = ",corrk_recombin
297     endif
298     
299     if (corrk .and. ngrid.eq.1) then
300       write(*,*) "simulate global averaged conditions ?"
301       global1d = .false. ! default value
302       call getin_p("global1d",global1d)
303       write(*,*) " global1d = ",global1d
304       
305       ! Test of incompatibility : if global1d is true, there should not be any diurnal cycle.
306       if (global1d.and.diurnal) then
307          write(*,*) "if global1d is true, diurnal must be set to false"
308          stop
309       endif
310
311       if (global1d) then
312          write(*,*) "Solar Zenith angle (deg.) ?"
313          write(*,*) "(assumed for averaged solar flux S/4)"
314          szangle=60.0  ! default value
315          call getin_p("szangle",szangle)
316          write(*,*) " szangle = ",szangle
317       endif
318     endif
319
320     write(*,*) "prohibit calculations outside corrk T grid?"
321     strictboundcorrk=.true. ! default value
322     call getin_p("strictboundcorrk",strictboundcorrk)
323     write(*,*) "strictboundcorrk = ",strictboundcorrk
324
325     write(*,*) "Minimum atmospheric temperature for Planck function integration ?"
326     tplanckmin=30.0 ! default value
327     call getin_p("tplanckmin",tplanckmin)
328     write(*,*) " tplanckmin = ",tplanckmin
329 
330     write(*,*) "Maximum atmospheric temperature for Planck function integration ?"
331     tplanckmax=1500.0 ! default value
332     call getin_p("tplanckmax",tplanckmax)
333     write(*,*) " tplanckmax = ",tplanckmax
334 
335     write(*,*) "Temperature step for Planck function integration ?"
336     dtplanck=0.1 ! default value
337     call getin_p("dtplanck",dtplanck)
338     write(*,*) " dtplanck = ",dtplanck
339 
340     write(*,*) "call gaseous absorption in the visible bands?", &
341                    "(matters only if callrad=T)"
342     callgasvis=.false. ! default value
343     call getin_p("callgasvis",callgasvis)
344     write(*,*) " callgasvis = ",callgasvis
345       
346     write(*,*) "call continuum opacities in radiative transfer ?", &
347                    "(matters only if callrad=T)"
348     continuum=.true. ! default value
349     call getin_p("continuum",continuum)
350     write(*,*) " continuum = ",continuum
351 
352     write(*,*) "version for H2H2 CIA file ?"
353     versH2H2cia=2011 ! default value (should be 2018 but retrocompatibility first)
354     call getin_p("versH2H2cia",versH2H2cia)
355     write(*,*) " versH2H2cia = ",versH2H2cia
356     ! Sanity check
357     if (versH2H2cia.ne.2011 .and. versH2H2cia.ne.2018) then
358        print*,'Error: Choose a correct value (2011 or 2018) for versH2H2cia !'
359        call abort
360     endif
361
362     write(*,*) "call turbulent vertical diffusion ?"
363     calldifv=.true. ! default value
364     call getin_p("calldifv",calldifv)
365     write(*,*) " calldifv = ",calldifv
366
367     write(*,*) "use turbdiff instead of vdifc ?"
368     UseTurbDiff=.true. ! default value
369     call getin_p("UseTurbDiff",UseTurbDiff)
370     write(*,*) " UseTurbDiff = ",UseTurbDiff
371
372     write(*,*) "call convective adjustment ?"
373     calladj=.true. ! default value
374     call getin_p("calladj",calladj)
375     write(*,*) " calladj = ",calladj
376
377     write(*,*) "Radiative timescale for Newtonian cooling ?"
378     tau_relax=30. ! default value
379     call getin_p("tau_relax",tau_relax)
380     write(*,*) " tau_relax = ",tau_relax
381     tau_relax=tau_relax*24*3600 ! convert Earth days --> seconds
382
383     write(*,*)"call thermal conduction in the soil ?"
384     callsoil=.true. ! default value
385     call getin_p("callsoil",callsoil)
386     write(*,*) " callsoil = ",callsoil
387         
388     write(*,*)"Rad transfer is computed every iradia", &
389                   " physical timestep"
390     iradia=1 ! default value
391     call getin_p("iradia",iradia)
392     write(*,*)" iradia = ",iradia
393       
394     write(*,*)"Rayleigh scattering ?"
395     rayleigh=.false.
396     call getin_p("rayleigh",rayleigh)
397     write(*,*)" rayleigh = ",rayleigh
398
399     write(*,*) "Use blackbody for stellar spectrum ?"
400     stelbbody=.false. ! default value
401     call getin_p("stelbbody",stelbbody)
402     write(*,*) " stelbbody = ",stelbbody
403
404     write(*,*) "Stellar blackbody temperature ?"
405     stelTbb=5800.0 ! default value
406     call getin_p("stelTbb",stelTbb)
407     write(*,*) " stelTbb = ",stelTbb
408
409     write(*,*)"Output mean OLR in 1D?"
410     meanOLR=.false.
411     call getin_p("meanOLR",meanOLR)
412     write(*,*)" meanOLR = ",meanOLR
413
414     write(*,*)"Output spectral OLR in 3D?"
415     specOLR=.false.
416     call getin_p("specOLR",specOLR)
417     write(*,*)" specOLR = ",specOLR
418
419     write(*,*)"Output diagnostic optical thickness attenuation exp(-tau)?"
420     diagdtau=.false.
421     call getin_p("diagdtau",diagdtau)
422     write(*,*)" diagdtau = ",diagdtau
423
424     write(*,*)"Uniform absorption in radiative transfer?"
425     graybody=.false.
426     call getin_p("graybody",graybody)
427     write(*,*)" graybody = ",graybody
428
429! Chemistry
430
431     write(*,*) "Run with or without chemistry?"
432     callchim=.false. ! default value
433     call getin_p("callchim",callchim)
434     write(*,*) " callchim = ",callchim
435
436     ! sanity check
437     if (callchim.and.(.not.tracer)) then
438       print*,"You are running chemistry without tracer"
439       print*,"Please start again with tracer =.true."
440       stop
441     endif
442     
443     write(*,*)"Chemistry is computed every ichim", &
444                   " physical timestep"
445     ichim=1 ! default value
446     call getin_p("ichim",ichim)
447     write(*,*)" ichim = ",ichim
448
449! Microphysics
450
451     write(*,*) "Use haze seasonal model from Karkoschka 2016 ?"
452     seashaze=.true. ! default value
453     call getin_p("seashaze",seashaze)
454     write(*,*)" seashaze = ",seashaze
455
456     write(*,*) "Run with or without microphysics?"
457     callmufi=.false. ! default value
458     call getin_p("callmufi",callmufi)
459     write(*,*)" callmufi = ",callmufi
460
461     ! sanity check
462     if (callmufi.and.(.not.tracer)) then
463       print*,"You are running microphysics without tracer"
464       print*,"Please start again with tracer =.true."
465       stop
466     endif
467
468     write(*,*) "Compute clouds?"
469     callclouds=.false. ! default value
470     call getin_p("callclouds",callclouds)
471     write(*,*)" callclouds = ",callclouds
472
473     ! sanity check
474     if (callclouds.and.(.not.callmufi)) then
475       print*,"You are trying to make clouds without microphysics !"
476       print*,"Please start again with callmufi =.true."
477       stop
478     endif
479
480     write(*,*) "Disable the coupling of microphysics within rad. transf. ?"
481     write(*,*) "If disabled we will assume a planetwide vert. profile of extinction ..."
482     uncoupl_optic_haze=.true. ! default value - true as long as the microphysics is bugged
483     call getin_p("uncoupl_optic_haze",uncoupl_optic_haze)
484     write(*,*)" uncoupl_optic_haze = ",uncoupl_optic_haze
485
486     write(*,*) "Pressure level of aer. production (Pa) ?"
487     p_prod=1.0 ! default value
488     call getin_p("p_prod",p_prod)
489     write(*,*)" p_prod = ",p_prod
490     
491     write(*,*) "Aerosol production rate (kg.m-2.s-1) ?"
492     tx_prod=3.5e-13 ! default value
493     call getin_p("tx_prod",tx_prod)
494     write(*,*)" tx_prod = ",tx_prod
495
496     write(*,*) "Equivalent radius production (m) ?"
497     rc_prod=2.0e-8 ! default value
498     call getin_p("rc_prod",rc_prod)
499     write(*,*)" rhc_prod = ",rc_prod
500
501     write(*,*) "Radius of air (nitrogen) molecule (m) ?"
502     air_rad=1.75e-10 ! default value
503     call getin_p("air_rad",air_rad)
504     write(*,*)" air_rad = ",air_rad
505
506     write(*,*) "Path to microphys. config file ?"
507     config_mufi='datagcm/microphysics/config.cfg' ! default value
508     call getin_p("config_mufi",config_mufi)
509     write(*,*)" config_mufi = ",config_mufi
510
511! Soil model
512     write(*,*)"Number of sub-surface layers for soil scheme?"
513     ! default value of nsoilmx set in comsoil_h
514     call getin_p("nsoilmx",nsoilmx)
515     write(*,*)" nsoilmx=",nsoilmx
516     
517     write(*,*)"Thickness of topmost soil layer (m)?"
518     ! default value of lay1_soil set in comsoil_h
519     call getin_p("lay1_soil",lay1_soil)
520     write(*,*)" lay1_soil = ",lay1_soil
521     
522     write(*,*)"Coefficient for soil layer thickness distribution?"
523     ! default value of alpha_soil set in comsoil_h
524     call getin_p("alpha_soil",alpha_soil)
525     write(*,*)" alpha_soil = ",alpha_soil
526
527     write(*,*)"Remove lower boundary?"
528     nosurf=.false.
529     call getin_p("nosurf",nosurf)
530     write(*,*)" nosurf = ",nosurf
531
532! Tests of incompatibility:
533     if (nosurf.and.callsoil) then
534       print*,'nosurf not compatible with soil scheme!'
535       print*,'... got to make a choice!'
536       call abort
537     endif
538
539     write(*,*)"Add an internal heat flux?", &
540                   "... matters only if callsoil=F"
541     intheat=0.
542     call getin_p("intheat",intheat)
543     write(*,*)" intheat = ",intheat
544
545     write(*,*)"Use Newtonian cooling for radiative transfer?"
546     newtonian=.false.
547     call getin_p("newtonian",newtonian)
548     write(*,*)" newtonian = ",newtonian
549
550! Tests of incompatibility:
551     if (newtonian.and.corrk) then
552       print*,'newtonian not compatible with correlated-k!'
553       call abort
554     endif
555     if (newtonian.and.calladj) then
556       print*,'newtonian not compatible with adjustment!'
557       call abort
558     endif
559     if (newtonian.and.calldifv) then
560       print*,'newtonian not compatible with a boundary layer!'
561       call abort
562     endif
563
564     write(*,*)"Test physics timescale in 1D?"
565     testradtimes=.false.
566     call getin_p("testradtimes",testradtimes)
567     write(*,*)" testradtimes = ",testradtimes
568
569! Test of incompatibility:
570! if testradtimes used, we must be in 1D
571     if (testradtimes.and.(ngrid.gt.1)) then
572       print*,'testradtimes can only be used in 1D!'
573       call abort
574     endif
575
576     write(*,*)"Which star?"
577     startype=1 ! default value = Sol
578     call getin_p("startype",startype)
579     write(*,*)" startype = ",startype
580
581     write(*,*)"Value of stellar flux at 1 AU?"
582     Fat1AU=1356.0 ! default value = Sol today
583     call getin_p("Fat1AU",Fat1AU)
584     write(*,*)" Fat1AU = ",Fat1AU
585
586     write(*,*) "Does user want to force cpp and mugaz?"
587     force_cpp=.false. ! default value
588     call getin_p("force_cpp",force_cpp)
589     write(*,*) " force_cpp = ",force_cpp
590
591     if (force_cpp) then
592       mugaz = -99999.
593       PRINT *,'MEAN MOLECULAR MASS in g mol-1 ?'
594       call getin_p("mugaz",mugaz)
595       IF (mugaz.eq.-99999.) THEN
596           PRINT *, "mugaz must be set if force_cpp = T"
597           STOP
598       ELSE
599           write(*,*) "mugaz=",mugaz
600       ENDIF
601       cpp = -99999.
602       PRINT *,'SPECIFIC HEAT CAPACITY in J K-1 kg-1 ?'
603       call getin_p("cpp",cpp)
604       IF (cpp.eq.-99999.) THEN
605           PRINT *, "cpp must be set if force_cpp = T"
606           STOP
607       ELSE
608           write(*,*) "cpp=",cpp
609       ENDIF
610     endif ! of if (force_cpp)
611     
612     call su_gases(nlayer,tracer)     
613     call calc_cpp_mugaz
614
615     PRINT*,'--------------------------------------------'
616     PRINT*
617     PRINT*
618  ELSE
619     write(*,*)
620     write(*,*) 'Cannot read file callphys.def. Is it here ?'
621     stop
622  ENDIF ! of IF(iscallphys)
623
624  PRINT*
625  PRINT*,'inifis: daysec',daysec
626  PRINT*
627  PRINT*,'inifis: The radiative transfer is computed:'
628  PRINT*,'           each ',iradia,' physical time-step'
629  PRINT*,'        or each ',iradia*dtphys,' seconds'
630  PRINT*
631  PRINT*,'inifis: Chemistry is computed:'
632  PRINT*,'           each ',ichim,' physical time-step'
633  PRINT*,'        or each ',ichim*dtphys,' seconds'
634  PRINT*
635
636!-----------------------------------------------------------------------
637!     Some more initialization:
638!     ------------------------
639
640  ! Initializations for comgeomfi_h
641#ifndef MESOSCALE
642  totarea=SSUM(ngrid,parea,1)
643  call planetwide_sumval(parea,totarea_planet)
644
645  !! those are defined in comdiurn_h.F90
646  IF (.not.ALLOCATED(sinlat)) ALLOCATE(sinlat(ngrid))
647  IF (.not.ALLOCATED(coslat)) ALLOCATE(coslat(ngrid))
648  IF (.not.ALLOCATED(sinlon)) ALLOCATE(sinlon(ngrid))
649  IF (.not.ALLOCATED(coslon)) ALLOCATE(coslon(ngrid))
650
651  DO ig=1,ngrid
652     sinlat(ig)=sin(plat(ig))
653     coslat(ig)=cos(plat(ig))
654     sinlon(ig)=sin(plon(ig))
655     coslon(ig)=cos(plon(ig))
656  ENDDO
657#endif
658  ! initialize variables in radinc_h
659  call ini_radinc_h(nlayer,tplanckmin,tplanckmax,dtplanck)
660 
661  ! allocate "comsoil_h" arrays
662  call ini_comsoil_h(ngrid)
663   
664  END SUBROUTINE inifis
665
666END MODULE inifis_mod
Note: See TracBrowser for help on using the repository browser.