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

Last change on this file since 3094 was 3090, checked in by slebonnois, 15 months ago

BdeBatz? : Cleans microphysics and makes few corrections for physics

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