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

Last change on this file since 2955 was 2366, checked in by jvatant, 5 years ago

Titan GCM : Major maintenance catching up commits from the generic including :

  • r2356 and 2354 removing obsolete old dynamical core
  • various minor addition to physics and gestion of phys_state_var_mode, especially in dyn1d
  • adding MESOSCALE CPP keys around chemistry and microphysics (disabled in mesoscale for now)
File size: 20.5 KB
RevLine 
[1524]1MODULE inifis_mod
2IMPLICIT NONE
[253]3
[1524]4CONTAINS
[253]5
[1524]6  SUBROUTINE inifis(ngrid,nlayer,nq, &
[1525]7             day_ini,pdaysec,nday,ptimestep, &
[1524]8             plat,plon,parea, &
9             prad,pg,pr,pcpp)
10
[1896]11  use init_print_control_mod, only: init_print_control
[1788]12  use radinc_h, only: ini_radinc_h
[1524]13  use comdiurn_h, only: sinlat, coslat, sinlon, coslon
[1542]14  use comgeomfi_h, only: totarea, totarea_planet
[1538]15  use comsoil_h, only: ini_comsoil_h, nsoilmx, lay1_soil, alpha_soil
[1525]16  use time_phylmdz_mod, only: ecritphy,day_step,iphysiq, &
17                              init_time, daysec, dtphys
[1524]18  use comcstfi_mod, only: rad, cpp, g, r, rcp, &
[1672]19                          mugaz, pi, avocado, kbol
[1524]20  use planete_mod, only: nres
21  use planetwide_mod, only: planetwide_sumval
22  use callkeys_mod
[1529]23  use mod_phys_lmdz_para, only : is_parallel
[1524]24
[135]25!=======================================================================
26!
27!   purpose:
28!   -------
29!
30!   Initialisation for the physical parametrisations of the LMD
[305]31!   Generic Model.
[135]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!   -------------
[2366]60  use datafile_mod
[1524]61  use ioipsl_getin_p_mod, only: getin_p
62  IMPLICIT NONE
[1384]63
[135]64
65
[1524]66  REAL,INTENT(IN) :: prad,pg,pr,pcpp,pdaysec,ptimestep
[1525]67  INTEGER,INTENT(IN) :: nday
[1524]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
[135]72 
[1524]73  EXTERNAL iniorbit,orbite
74  EXTERNAL SSUM
75  REAL SSUM
[135]76 
[1896]77  ! Initialize flags lunout, prt_level, debug (in print_control_mod)
78  CALL init_print_control
79
[1524]80  ! initialize constants in comcstfi_mod
81  rad=prad
82  cpp=pcpp
83  g=pg
84  r=pr
85  rcp=r/cpp
[2078]86  mugaz=8.314*1000./pr ! dummy init
[1524]87  pi=2.*asin(1.)
88  avocado = 6.02214179e23   ! added by RW
[1672]89  kbol = 1.38064852e-23  ! added by JVO for Titan chem
[135]90
[1524]91  ! Initialize some "temporal and calendar" related variables
[2366]92#ifndef MESOSCALE
[1525]93  CALL init_time(day_ini,pdaysec,nday,ptimestep)
[2366]94#endif
[135]95
[1525]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
[135]102
[1670]103  ! do we read a startphy.nc file? (default: .true.)
104  call getin_p("startphy_file",startphy_file)
105 
[135]106! --------------------------------------------------------------
107!  Reading the "callphys.def" file controlling some key options
108! --------------------------------------------------------------
109     
[1524]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
[135]114     
[1315]115!!!      IF(ierr.EQ.0) THEN
[1524]116  IF(iscallphys) THEN
117     PRINT*
118     PRINT*
119     PRINT*,'--------------------------------------------'
120     PRINT*,' inifis: Parametres pour la physique (callphys.def)'
121     PRINT*,'--------------------------------------------'
[135]122
[1524]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)
[374]127
[1524]128     write(*,*) "Run with or without tracer transport ?"
129     tracer=.false. ! default value
130     call getin_p("tracer",tracer)
131     write(*,*) " tracer = ",tracer
[135]132
[1524]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
[728]138
[1524]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
[135]144
[1524]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
[2366]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
[135]156
[1524]157     write(*,*) "Tidally resonant rotation ?"
158     tlocked=.false. ! default value
159     call getin_p("tlocked",tlocked)
160     write(*,*) "tlocked = ",tlocked
[135]161
[1524]162     write(*,*) "Saturn ring shadowing ?"
163     rings_shadow = .false.
164     call getin_p("rings_shadow", rings_shadow)
165     write(*,*) "rings_shadow = ", rings_shadow
[1133]166         
[1524]167     write(*,*) "Compute latitude-dependent gravity field?"
168     oblate = .false.
169     call getin_p("oblate", oblate)
170     write(*,*) "oblate = ", oblate
[1194]171
[1524]172     write(*,*) "Flattening of the planet (a-b)/a "
173     flatten = 0.0
174     call getin_p("flatten", flatten)
[1672]175     write(*,*) "flatten = ", flatten         
[1194]176
[1524]177     write(*,*) "Needed if oblate=.true.: J2"
178     J2 = 0.0
179     call getin_p("J2", J2)
180     write(*,*) "J2 = ", J2
[1194]181         
[1524]182     write(*,*) "Needed if oblate=.true.: Planet mass (*1e24 kg)"
183     MassPlanet = 0.0
184     call getin_p("MassPlanet", MassPlanet)
185     write(*,*) "MassPlanet = ", MassPlanet         
[1194]186
[1524]187     write(*,*) "Needed if oblate=.true.: Planet mean radius (m)"
188     Rmean = 0.0
189     call getin_p("Rmean", Rmean)
190     write(*,*) "Rmean = ", Rmean
[1947]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
[2241]196     
197     ! sanity check warning
198     if (eff_gz) then
199       print*,"WARNING : You run chemistry with effective altitude-dependent gravity field !!"
200       print*,"You will have no coherence in your heating rates between physics and dynamics !!"
201       print*,"I let you continue but you should rather set eff_gz =.false. ..."
202     endif
203
[1194]204         
[135]205! Test of incompatibility:
206! if tlocked, then diurnal should be false
[1524]207     if (tlocked.and.diurnal) then
208       print*,'If diurnal=true, we should turn off tlocked.'
209       stop
210     endif
[135]211
[1524]212     write(*,*) "Tidal resonance ratio ?"
213     nres=0          ! default value
214     call getin_p("nres",nres)
215     write(*,*) "nres = ",nres
[135]216
[1524]217     write(*,*) "Write some extra output to the screen ?"
218     lwrite=.false. ! default value
219     call getin_p("lwrite",lwrite)
220     write(*,*) " lwrite = ",lwrite
[135]221
[1524]222     write(*,*) "Save statistics in file stats.nc ?"
223     callstats=.true. ! default value
224     call getin_p("callstats",callstats)
225     write(*,*) " callstats = ",callstats
[135]226
[1524]227     write(*,*) "Test energy conservation of model physics ?"
228     enertest=.false. ! default value
229     call getin_p("enertest",enertest)
230     write(*,*) " enertest = ",enertest
[135]231
[1524]232     write(*,*) "Check to see if cpp values used match gases.def ?"
233     check_cpp_match=.true. ! default value
234     call getin_p("check_cpp_match",check_cpp_match)
235     write(*,*) " check_cpp_match = ",check_cpp_match
[538]236
[1524]237     write(*,*) "call radiative transfer ?"
238     callrad=.true. ! default value
239     call getin_p("callrad",callrad)
240     write(*,*) " callrad = ",callrad
[135]241
[1524]242     write(*,*) "call correlated-k radiative transfer ?"
243     corrk=.true. ! default value
244     call getin_p("corrk",corrk)
245     write(*,*) " corrk = ",corrk
[1822]246     
247     if (corrk) then
248       ! default path is set in datadir
249       write(*,*) "callcorrk: Correlated-k data base folder:",trim(datadir)
250       call getin_p("corrkdir",corrkdir)
251       write(*,*) " corrkdir = ",corrkdir
[2050]252       
253       write(*,*) "use correlated-k recombination instead of pre-mixed values ?"
[2241]254       corrk_recombin=.false.! default value
[2050]255       call getin_p("corrk_recombin",corrk_recombin)
256       write(*,*) " corrk_recombin = ",corrk_recombin
[1822]257     endif
258     
259     if (corrk .and. ngrid.eq.1) then
260       write(*,*) "simulate global averaged conditions ?"
261       global1d = .false. ! default value
262       call getin_p("global1d",global1d)
263       write(*,*) " global1d = ",global1d
264       
265       ! Test of incompatibility : if global1d is true, there should not be any diurnal cycle.
266       if (global1d.and.diurnal) then
267          write(*,*) "if global1d is true, diurnal must be set to false"
268          stop
269       endif
[135]270
[1822]271       if (global1d) then
272          write(*,*) "Solar Zenith angle (deg.) ?"
273          write(*,*) "(assumed for averaged solar flux S/4)"
274          szangle=60.0  ! default value
275          call getin_p("szangle",szangle)
276          write(*,*) " szangle = ",szangle
277       endif
278     endif
279
[1524]280     write(*,*) "prohibit calculations outside corrk T grid?"
281     strictboundcorrk=.true. ! default value
282     call getin_p("strictboundcorrk",strictboundcorrk)
283     write(*,*) "strictboundcorrk = ",strictboundcorrk
[1145]284
[2366]285     write(*,*) "Minimum atmospheric temperature for Planck function integration ?"
286     tplanckmin=30.0 ! default value
287     call getin_p("tplanckmin",tplanckmin)
288     write(*,*) " tplanckmin = ",tplanckmin
289 
290     write(*,*) "Maximum atmospheric temperature for Planck function integration ?"
291     tplanckmax=1500.0 ! default value
292     call getin_p("tplanckmax",tplanckmax)
293     write(*,*) " tplanckmax = ",tplanckmax
294 
295     write(*,*) "Temperature step for Planck function integration ?"
296     dtplanck=0.1 ! default value
297     call getin_p("dtplanck",dtplanck)
298     write(*,*) " dtplanck = ",dtplanck
299 
[1524]300     write(*,*) "call gaseous absorption in the visible bands?", &
301                    "(matters only if callrad=T)"
302     callgasvis=.false. ! default value
303     call getin_p("callgasvis",callgasvis)
304     write(*,*) " callgasvis = ",callgasvis
[538]305       
[1524]306     write(*,*) "call continuum opacities in radiative transfer ?", &
307                    "(matters only if callrad=T)"
308     continuum=.true. ! default value
309     call getin_p("continuum",continuum)
310     write(*,*) " continuum = ",continuum
[538]311 
[2245]312     write(*,*) "version for H2H2 CIA file ?"
313     versH2H2cia=2011 ! default value (should be 2018 but retrocompatibility first)
314     call getin_p("versH2H2cia",versH2H2cia)
315     write(*,*) " versH2H2cia = ",versH2H2cia
316     ! Sanity check
317     if (versH2H2cia.ne.2011 .and. versH2H2cia.ne.2018) then
318        print*,'Error: Choose a correct value (2011 or 2018) for versH2H2cia !'
319        call abort
320     endif
321
[1524]322     write(*,*) "call turbulent vertical diffusion ?"
323     calldifv=.true. ! default value
324     call getin_p("calldifv",calldifv)
325     write(*,*) " calldifv = ",calldifv
[135]326
[1524]327     write(*,*) "use turbdiff instead of vdifc ?"
328     UseTurbDiff=.true. ! default value
329     call getin_p("UseTurbDiff",UseTurbDiff)
330     write(*,*) " UseTurbDiff = ",UseTurbDiff
[596]331
[1524]332     write(*,*) "call convective adjustment ?"
333     calladj=.true. ! default value
334     call getin_p("calladj",calladj)
335     write(*,*) " calladj = ",calladj
[135]336
[1524]337     write(*,*) "Radiative timescale for Newtonian cooling ?"
338     tau_relax=30. ! default value
339     call getin_p("tau_relax",tau_relax)
340     write(*,*) " tau_relax = ",tau_relax
341     tau_relax=tau_relax*24*3600 ! convert Earth days --> seconds
[253]342
[1524]343     write(*,*)"call thermal conduction in the soil ?"
344     callsoil=.true. ! default value
345     call getin_p("callsoil",callsoil)
346     write(*,*) " callsoil = ",callsoil
[135]347         
[1524]348     write(*,*)"Rad transfer is computed every iradia", &
349                   " physical timestep"
350     iradia=1 ! default value
351     call getin_p("iradia",iradia)
352     write(*,*)" iradia = ",iradia
[135]353       
[1524]354     write(*,*)"Rayleigh scattering ?"
355     rayleigh=.false.
356     call getin_p("rayleigh",rayleigh)
357     write(*,*)" rayleigh = ",rayleigh
[135]358
[1524]359     write(*,*) "Use blackbody for stellar spectrum ?"
360     stelbbody=.false. ! default value
361     call getin_p("stelbbody",stelbbody)
362     write(*,*) " stelbbody = ",stelbbody
[135]363
[1524]364     write(*,*) "Stellar blackbody temperature ?"
365     stelTbb=5800.0 ! default value
366     call getin_p("stelTbb",stelTbb)
367     write(*,*) " stelTbb = ",stelTbb
[253]368
[1524]369     write(*,*)"Output mean OLR in 1D?"
370     meanOLR=.false.
371     call getin_p("meanOLR",meanOLR)
372     write(*,*)" meanOLR = ",meanOLR
[135]373
[1524]374     write(*,*)"Output spectral OLR in 3D?"
375     specOLR=.false.
376     call getin_p("specOLR",specOLR)
377     write(*,*)" specOLR = ",specOLR
[135]378
[2138]379     write(*,*)"Output diagnostic optical thickness attenuation exp(-tau)?"
[2131]380     diagdtau=.false.
381     call getin_p("diagdtau",diagdtau)
382     write(*,*)" diagdtau = ",diagdtau
383
[1524]384     write(*,*)"Uniform absorption in radiative transfer?"
385     graybody=.false.
386     call getin_p("graybody",graybody)
387     write(*,*)" graybody = ",graybody
[253]388
[1672]389! Chemistry
390
391     write(*,*) "Run with or without chemistry?"
392     callchim=.false. ! default value
393     call getin_p("callchim",callchim)
394     write(*,*) " callchim = ",callchim
395
396     ! sanity check
397     if (callchim.and.(.not.tracer)) then
398       print*,"You are running chemistry without tracer"
399       print*,"Please start again with tracer =.true."
400       stop
401     endif
[1947]402     
[1672]403     write(*,*)"Chemistry is computed every ichim", &
404                   " physical timestep"
405     ichim=1 ! default value
406     call getin_p("ichim",ichim)
407     write(*,*)" ichim = ",ichim
408
[1795]409! Microphysics
410
[2046]411     write(*,*) "Use haze seasonal model from Karkoschka 2016 ?"
412     seashaze=.true. ! default value
413     call getin_p("seashaze",seashaze)
414     write(*,*)" seashaze = ",seashaze
415
[1795]416     write(*,*) "Run with or without microphysics?"
417     callmufi=.false. ! default value
418     call getin_p("callmufi",callmufi)
419     write(*,*)" callmufi = ",callmufi
420
421     ! sanity check
422     if (callmufi.and.(.not.tracer)) then
423       print*,"You are running microphysics without tracer"
424       print*,"Please start again with tracer =.true."
425       stop
426     endif
427
428     write(*,*) "Compute clouds?"
429     callclouds=.false. ! default value
430     call getin_p("callclouds",callclouds)
431     write(*,*)" callclouds = ",callclouds
432
433     ! sanity check
434     if (callclouds.and.(.not.callmufi)) then
435       print*,"You are trying to make clouds without microphysics !"
436       print*,"Please start again with callmufi =.true."
437       stop
438     endif
439
[1897]440     write(*,*) "Disable the coupling of microphysics within rad. transf. ?"
441     write(*,*) "If disabled we will assume a planetwide vert. profile of extinction ..."
442     uncoupl_optic_haze=.true. ! default value - true as long as the microphysics is bugged
443     call getin_p("uncoupl_optic_haze",uncoupl_optic_haze)
444     write(*,*)" uncoupl_optic_haze = ",uncoupl_optic_haze
[1795]445
446     write(*,*) "Pressure level of aer. production (Pa) ?"
447     p_prod=1.0 ! default value
448     call getin_p("p_prod",p_prod)
[1822]449     write(*,*)" p_prod = ",p_prod
[1795]450     
451     write(*,*) "Aerosol production rate (kg.m-2.s-1) ?"
452     tx_prod=3.5e-13 ! default value
453     call getin_p("tx_prod",tx_prod)
[1822]454     write(*,*)" tx_prod = ",tx_prod
[1795]455
456     write(*,*) "Equivalent radius production (m) ?"
457     rc_prod=2.0e-8 ! default value
458     call getin_p("rc_prod",rc_prod)
[1822]459     write(*,*)" rhc_prod = ",rc_prod
[1795]460
461     write(*,*) "Radius of air (nitrogen) molecule (m) ?"
462     air_rad=1.75e-10 ! default value
463     call getin_p("air_rad",air_rad)
[1822]464     write(*,*)" air_rad = ",air_rad
[1795]465
466     write(*,*) "Path to microphys. config file ?"
467     config_mufi='datagcm/microphysics/config.cfg' ! default value
468     call getin_p("config_mufi",config_mufi)
[1822]469     write(*,*)" config_mufi = ",config_mufi
[1795]470
[1538]471! Soil model
472     write(*,*)"Number of sub-surface layers for soil scheme?"
473     ! default value of nsoilmx set in comsoil_h
474     call getin_p("nsoilmx",nsoilmx)
475     write(*,*)" nsoilmx=",nsoilmx
476     
477     write(*,*)"Thickness of topmost soil layer (m)?"
478     ! default value of lay1_soil set in comsoil_h
479     call getin_p("lay1_soil",lay1_soil)
480     write(*,*)" lay1_soil = ",lay1_soil
481     
482     write(*,*)"Coefficient for soil layer thickness distribution?"
483     ! default value of alpha_soil set in comsoil_h
484     call getin_p("alpha_soil",alpha_soil)
485     write(*,*)" alpha_soil = ",alpha_soil
486
[1524]487     write(*,*)"Remove lower boundary?"
488     nosurf=.false.
489     call getin_p("nosurf",nosurf)
490     write(*,*)" nosurf = ",nosurf
[253]491
492! Tests of incompatibility:
[1524]493     if (nosurf.and.callsoil) then
494       print*,'nosurf not compatible with soil scheme!'
495       print*,'... got to make a choice!'
496       call abort
497     endif
[253]498
[1524]499     write(*,*)"Add an internal heat flux?", &
500                   "... matters only if callsoil=F"
501     intheat=0.
502     call getin_p("intheat",intheat)
503     write(*,*)" intheat = ",intheat
[952]504
[1524]505     write(*,*)"Use Newtonian cooling for radiative transfer?"
506     newtonian=.false.
507     call getin_p("newtonian",newtonian)
508     write(*,*)" newtonian = ",newtonian
[253]509
510! Tests of incompatibility:
[1524]511     if (newtonian.and.corrk) then
512       print*,'newtonian not compatible with correlated-k!'
513       call abort
514     endif
515     if (newtonian.and.calladj) then
516       print*,'newtonian not compatible with adjustment!'
517       call abort
518     endif
519     if (newtonian.and.calldifv) then
520       print*,'newtonian not compatible with a boundary layer!'
521       call abort
522     endif
[253]523
[1524]524     write(*,*)"Test physics timescale in 1D?"
525     testradtimes=.false.
526     call getin_p("testradtimes",testradtimes)
527     write(*,*)" testradtimes = ",testradtimes
[253]528
529! Test of incompatibility:
530! if testradtimes used, we must be in 1D
[1524]531     if (testradtimes.and.(ngrid.gt.1)) then
532       print*,'testradtimes can only be used in 1D!'
533       call abort
534     endif
[253]535
[1524]536     write(*,*)"Which star?"
537     startype=1 ! default value = Sol
538     call getin_p("startype",startype)
539     write(*,*)" startype = ",startype
[135]540
[1524]541     write(*,*)"Value of stellar flux at 1 AU?"
542     Fat1AU=1356.0 ! default value = Sol today
543     call getin_p("Fat1AU",Fat1AU)
544     write(*,*)" Fat1AU = ",Fat1AU
[135]545
[1524]546     write(*,*) "Does user want to force cpp and mugaz?"
547     force_cpp=.false. ! default value
548     call getin_p("force_cpp",force_cpp)
549     write(*,*) " force_cpp = ",force_cpp
[589]550
[1524]551     if (force_cpp) then
552       mugaz = -99999.
553       PRINT *,'MEAN MOLECULAR MASS in g mol-1 ?'
554       call getin_p("mugaz",mugaz)
555       IF (mugaz.eq.-99999.) THEN
556           PRINT *, "mugaz must be set if force_cpp = T"
557           STOP
558       ELSE
559           write(*,*) "mugaz=",mugaz
560       ENDIF
561       cpp = -99999.
562       PRINT *,'SPECIFIC HEAT CAPACITY in J K-1 kg-1 ?'
563       call getin_p("cpp",cpp)
564       IF (cpp.eq.-99999.) THEN
565           PRINT *, "cpp must be set if force_cpp = T"
566           STOP
567       ELSE
568           write(*,*) "cpp=",cpp
569       ENDIF
570     endif ! of if (force_cpp)
[1648]571     
572     call su_gases(nlayer,tracer)     
[2366]573     call calc_cpp_mugaz
574
[1524]575     PRINT*,'--------------------------------------------'
576     PRINT*
577     PRINT*
578  ELSE
579     write(*,*)
580     write(*,*) 'Cannot read file callphys.def. Is it here ?'
581     stop
582  ENDIF ! of IF(iscallphys)
[135]583
[1524]584  PRINT*
585  PRINT*,'inifis: daysec',daysec
586  PRINT*
587  PRINT*,'inifis: The radiative transfer is computed:'
588  PRINT*,'           each ',iradia,' physical time-step'
589  PRINT*,'        or each ',iradia*dtphys,' seconds'
590  PRINT*
[1672]591  PRINT*,'inifis: Chemistry is computed:'
592  PRINT*,'           each ',ichim,' physical time-step'
593  PRINT*,'        or each ',ichim*dtphys,' seconds'
594  PRINT*
[135]595
596!-----------------------------------------------------------------------
597!     Some more initialization:
598!     ------------------------
599
[1542]600  ! Initializations for comgeomfi_h
[2366]601#ifndef MESOSCALE
[1542]602  totarea=SSUM(ngrid,parea,1)
603  call planetwide_sumval(parea,totarea_planet)
[787]604
[1524]605  !! those are defined in comdiurn_h.F90
606  IF (.not.ALLOCATED(sinlat)) ALLOCATE(sinlat(ngrid))
607  IF (.not.ALLOCATED(coslat)) ALLOCATE(coslat(ngrid))
608  IF (.not.ALLOCATED(sinlon)) ALLOCATE(sinlon(ngrid))
609  IF (.not.ALLOCATED(coslon)) ALLOCATE(coslon(ngrid))
[787]610
[1524]611  DO ig=1,ngrid
612     sinlat(ig)=sin(plat(ig))
613     coslat(ig)=cos(plat(ig))
614     sinlon(ig)=sin(plon(ig))
615     coslon(ig)=cos(plon(ig))
616  ENDDO
[2366]617#endif
[1722]618  ! initialize variables in radinc_h
[2366]619  call ini_radinc_h(nlayer,tplanckmin,tplanckmax,dtplanck)
[1529]620 
[1524]621  ! allocate "comsoil_h" arrays
622  call ini_comsoil_h(ngrid)
[2366]623   
[1524]624  END SUBROUTINE inifis
[135]625
[1524]626END MODULE inifis_mod
Note: See TracBrowser for help on using the repository browser.