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

Last change on this file since 2046 was 2046, checked in by jvatant, 6 years ago

Add a simple seasonal+latitudinal variation model (season_haze.F90) for the vertical mean profile
of haze. Based on Karkoscha,2016 . Activable through "seashaze" key (default=T).
--JVO

File size: 18.8 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 datafile_mod
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, kbol
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 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  pi=2.*asin(1.)
87  avocado = 6.02214179e23   ! added by RW
88  kbol = 1.38064852e-23  ! added by JVO for Titan chem
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     write(*,*) "Needed if oblate=.true.: J2"
170     J2 = 0.0
171     call getin_p("J2", J2)
172     write(*,*) "J2 = ", J2
173         
174     write(*,*) "Needed if oblate=.true.: Planet mass (*1e24 kg)"
175     MassPlanet = 0.0
176     call getin_p("MassPlanet", MassPlanet)
177     write(*,*) "MassPlanet = ", MassPlanet         
178
179     write(*,*) "Needed if oblate=.true.: Planet mean radius (m)"
180     Rmean = 0.0
181     call getin_p("Rmean", Rmean)
182     write(*,*) "Rmean = ", Rmean
183     
184     write(*,*) "Compute effective altitude-dependent gravity field?"
185     eff_gz = .false.
186     call getin_p("eff_gz", eff_gz)
187     write(*,*) "eff_gz = ", eff_gz
188         
189! Test of incompatibility:
190! if tlocked, then diurnal should be false
191     if (tlocked.and.diurnal) then
192       print*,'If diurnal=true, we should turn off tlocked.'
193       stop
194     endif
195
196     write(*,*) "Tidal resonance ratio ?"
197     nres=0          ! default value
198     call getin_p("nres",nres)
199     write(*,*) "nres = ",nres
200
201     write(*,*) "Write some extra output to the screen ?"
202     lwrite=.false. ! default value
203     call getin_p("lwrite",lwrite)
204     write(*,*) " lwrite = ",lwrite
205
206     write(*,*) "Save statistics in file stats.nc ?"
207     callstats=.true. ! default value
208     call getin_p("callstats",callstats)
209     write(*,*) " callstats = ",callstats
210
211     write(*,*) "Test energy conservation of model physics ?"
212     enertest=.false. ! default value
213     call getin_p("enertest",enertest)
214     write(*,*) " enertest = ",enertest
215
216     write(*,*) "Check to see if cpp values used match gases.def ?"
217     check_cpp_match=.true. ! default value
218     call getin_p("check_cpp_match",check_cpp_match)
219     write(*,*) " check_cpp_match = ",check_cpp_match
220
221     write(*,*) "call radiative transfer ?"
222     callrad=.true. ! default value
223     call getin_p("callrad",callrad)
224     write(*,*) " callrad = ",callrad
225
226     write(*,*) "call correlated-k radiative transfer ?"
227     corrk=.true. ! default value
228     call getin_p("corrk",corrk)
229     write(*,*) " corrk = ",corrk
230     
231     if (corrk) then
232       ! default path is set in datadir
233       write(*,*) "callcorrk: Correlated-k data base folder:",trim(datadir)
234       call getin_p("corrkdir",corrkdir)
235       write(*,*) " corrkdir = ",corrkdir
236     endif
237     
238     if (corrk .and. ngrid.eq.1) then
239       write(*,*) "simulate global averaged conditions ?"
240       global1d = .false. ! default value
241       call getin_p("global1d",global1d)
242       write(*,*) " global1d = ",global1d
243       
244       ! Test of incompatibility : if global1d is true, there should not be any diurnal cycle.
245       if (global1d.and.diurnal) then
246          write(*,*) "if global1d is true, diurnal must be set to false"
247          stop
248       endif
249
250       if (global1d) then
251          write(*,*) "Solar Zenith angle (deg.) ?"
252          write(*,*) "(assumed for averaged solar flux S/4)"
253          szangle=60.0  ! default value
254          call getin_p("szangle",szangle)
255          write(*,*) " szangle = ",szangle
256       endif
257     endif
258
259     write(*,*) "prohibit calculations outside corrk T grid?"
260     strictboundcorrk=.true. ! default value
261     call getin_p("strictboundcorrk",strictboundcorrk)
262     write(*,*) "strictboundcorrk = ",strictboundcorrk
263
264     write(*,*) "call gaseous absorption in the visible bands?", &
265                    "(matters only if callrad=T)"
266     callgasvis=.false. ! default value
267     call getin_p("callgasvis",callgasvis)
268     write(*,*) " callgasvis = ",callgasvis
269       
270     write(*,*) "call continuum opacities in radiative transfer ?", &
271                    "(matters only if callrad=T)"
272     continuum=.true. ! default value
273     call getin_p("continuum",continuum)
274     write(*,*) " continuum = ",continuum
275 
276     write(*,*) "call turbulent vertical diffusion ?"
277     calldifv=.true. ! default value
278     call getin_p("calldifv",calldifv)
279     write(*,*) " calldifv = ",calldifv
280
281     write(*,*) "use turbdiff instead of vdifc ?"
282     UseTurbDiff=.true. ! default value
283     call getin_p("UseTurbDiff",UseTurbDiff)
284     write(*,*) " UseTurbDiff = ",UseTurbDiff
285
286     write(*,*) "call convective adjustment ?"
287     calladj=.true. ! default value
288     call getin_p("calladj",calladj)
289     write(*,*) " calladj = ",calladj
290
291     write(*,*) "Radiative timescale for Newtonian cooling ?"
292     tau_relax=30. ! default value
293     call getin_p("tau_relax",tau_relax)
294     write(*,*) " tau_relax = ",tau_relax
295     tau_relax=tau_relax*24*3600 ! convert Earth days --> seconds
296
297     write(*,*)"call thermal conduction in the soil ?"
298     callsoil=.true. ! default value
299     call getin_p("callsoil",callsoil)
300     write(*,*) " callsoil = ",callsoil
301         
302     write(*,*)"Rad transfer is computed every iradia", &
303                   " physical timestep"
304     iradia=1 ! default value
305     call getin_p("iradia",iradia)
306     write(*,*)" iradia = ",iradia
307       
308     write(*,*)"Rayleigh scattering ?"
309     rayleigh=.false.
310     call getin_p("rayleigh",rayleigh)
311     write(*,*)" rayleigh = ",rayleigh
312
313     write(*,*) "Use blackbody for stellar spectrum ?"
314     stelbbody=.false. ! default value
315     call getin_p("stelbbody",stelbbody)
316     write(*,*) " stelbbody = ",stelbbody
317
318     write(*,*) "Stellar blackbody temperature ?"
319     stelTbb=5800.0 ! default value
320     call getin_p("stelTbb",stelTbb)
321     write(*,*) " stelTbb = ",stelTbb
322
323     write(*,*)"Output mean OLR in 1D?"
324     meanOLR=.false.
325     call getin_p("meanOLR",meanOLR)
326     write(*,*)" meanOLR = ",meanOLR
327
328     write(*,*)"Output spectral OLR in 3D?"
329     specOLR=.false.
330     call getin_p("specOLR",specOLR)
331     write(*,*)" specOLR = ",specOLR
332
333     write(*,*)"Uniform absorption in radiative transfer?"
334     graybody=.false.
335     call getin_p("graybody",graybody)
336     write(*,*)" graybody = ",graybody
337
338! Chemistry
339
340     write(*,*) "Run with or without chemistry?"
341     callchim=.false. ! default value
342     call getin_p("callchim",callchim)
343     write(*,*) " callchim = ",callchim
344
345     ! sanity check
346     if (callchim.and.(.not.tracer)) then
347       print*,"You are running chemistry without tracer"
348       print*,"Please start again with tracer =.true."
349       stop
350     endif
351     
352     ! sanity check warning
353     if (callchim.and.(.not.eff_gz)) then
354       print*,"WARNING : You run chemistry without effective altitude-dependent gravity field !!"
355       print*,"You will have wrong vertical photodissociations rates, that's crazy !!"
356       print*,"I let you continue but you should rather set eff_gz =.true. ..."
357       !stop
358     endif
359
360
361     write(*,*)"Chemistry is computed every ichim", &
362                   " physical timestep"
363     ichim=1 ! default value
364     call getin_p("ichim",ichim)
365     write(*,*)" ichim = ",ichim
366
367! Microphysics
368
369     write(*,*) "Use haze seasonal model from Karkoschka 2016 ?"
370     seashaze=.true. ! default value
371     call getin_p("seashaze",seashaze)
372     write(*,*)" seashaze = ",seashaze
373
374     write(*,*) "Run with or without microphysics?"
375     callmufi=.false. ! default value
376     call getin_p("callmufi",callmufi)
377     write(*,*)" callmufi = ",callmufi
378
379     ! sanity check
380     if (callmufi.and.(.not.tracer)) then
381       print*,"You are running microphysics without tracer"
382       print*,"Please start again with tracer =.true."
383       stop
384     endif
385
386     write(*,*) "Compute clouds?"
387     callclouds=.false. ! default value
388     call getin_p("callclouds",callclouds)
389     write(*,*)" callclouds = ",callclouds
390
391     ! sanity check
392     if (callclouds.and.(.not.callmufi)) then
393       print*,"You are trying to make clouds without microphysics !"
394       print*,"Please start again with callmufi =.true."
395       stop
396     endif
397
398     write(*,*) "Disable the coupling of microphysics within rad. transf. ?"
399     write(*,*) "If disabled we will assume a planetwide vert. profile of extinction ..."
400     uncoupl_optic_haze=.true. ! default value - true as long as the microphysics is bugged
401     call getin_p("uncoupl_optic_haze",uncoupl_optic_haze)
402     write(*,*)" uncoupl_optic_haze = ",uncoupl_optic_haze
403
404     write(*,*) "Pressure level of aer. production (Pa) ?"
405     p_prod=1.0 ! default value
406     call getin_p("p_prod",p_prod)
407     write(*,*)" p_prod = ",p_prod
408     
409     write(*,*) "Aerosol production rate (kg.m-2.s-1) ?"
410     tx_prod=3.5e-13 ! default value
411     call getin_p("tx_prod",tx_prod)
412     write(*,*)" tx_prod = ",tx_prod
413
414     write(*,*) "Equivalent radius production (m) ?"
415     rc_prod=2.0e-8 ! default value
416     call getin_p("rc_prod",rc_prod)
417     write(*,*)" rhc_prod = ",rc_prod
418
419     write(*,*) "Radius of air (nitrogen) molecule (m) ?"
420     air_rad=1.75e-10 ! default value
421     call getin_p("air_rad",air_rad)
422     write(*,*)" air_rad = ",air_rad
423
424     write(*,*) "Path to microphys. config file ?"
425     config_mufi='datagcm/microphysics/config.cfg' ! default value
426     call getin_p("config_mufi",config_mufi)
427     write(*,*)" config_mufi = ",config_mufi
428
429! Soil model
430     write(*,*)"Number of sub-surface layers for soil scheme?"
431     ! default value of nsoilmx set in comsoil_h
432     call getin_p("nsoilmx",nsoilmx)
433     write(*,*)" nsoilmx=",nsoilmx
434     
435     write(*,*)"Thickness of topmost soil layer (m)?"
436     ! default value of lay1_soil set in comsoil_h
437     call getin_p("lay1_soil",lay1_soil)
438     write(*,*)" lay1_soil = ",lay1_soil
439     
440     write(*,*)"Coefficient for soil layer thickness distribution?"
441     ! default value of alpha_soil set in comsoil_h
442     call getin_p("alpha_soil",alpha_soil)
443     write(*,*)" alpha_soil = ",alpha_soil
444
445     write(*,*)"Remove lower boundary?"
446     nosurf=.false.
447     call getin_p("nosurf",nosurf)
448     write(*,*)" nosurf = ",nosurf
449
450! Tests of incompatibility:
451     if (nosurf.and.callsoil) then
452       print*,'nosurf not compatible with soil scheme!'
453       print*,'... got to make a choice!'
454       call abort
455     endif
456
457     write(*,*)"Add an internal heat flux?", &
458                   "... matters only if callsoil=F"
459     intheat=0.
460     call getin_p("intheat",intheat)
461     write(*,*)" intheat = ",intheat
462
463     write(*,*)"Use Newtonian cooling for radiative transfer?"
464     newtonian=.false.
465     call getin_p("newtonian",newtonian)
466     write(*,*)" newtonian = ",newtonian
467
468! Tests of incompatibility:
469     if (newtonian.and.corrk) then
470       print*,'newtonian not compatible with correlated-k!'
471       call abort
472     endif
473     if (newtonian.and.calladj) then
474       print*,'newtonian not compatible with adjustment!'
475       call abort
476     endif
477     if (newtonian.and.calldifv) then
478       print*,'newtonian not compatible with a boundary layer!'
479       call abort
480     endif
481
482     write(*,*)"Test physics timescale in 1D?"
483     testradtimes=.false.
484     call getin_p("testradtimes",testradtimes)
485     write(*,*)" testradtimes = ",testradtimes
486
487! Test of incompatibility:
488! if testradtimes used, we must be in 1D
489     if (testradtimes.and.(ngrid.gt.1)) then
490       print*,'testradtimes can only be used in 1D!'
491       call abort
492     endif
493
494     write(*,*)"Which star?"
495     startype=1 ! default value = Sol
496     call getin_p("startype",startype)
497     write(*,*)" startype = ",startype
498
499     write(*,*)"Value of stellar flux at 1 AU?"
500     Fat1AU=1356.0 ! default value = Sol today
501     call getin_p("Fat1AU",Fat1AU)
502     write(*,*)" Fat1AU = ",Fat1AU
503
504     write(*,*) "Does user want to force cpp and mugaz?"
505     force_cpp=.false. ! default value
506     call getin_p("force_cpp",force_cpp)
507     write(*,*) " force_cpp = ",force_cpp
508
509     if (force_cpp) then
510       mugaz = -99999.
511       PRINT *,'MEAN MOLECULAR MASS in g mol-1 ?'
512       call getin_p("mugaz",mugaz)
513       IF (mugaz.eq.-99999.) THEN
514           PRINT *, "mugaz must be set if force_cpp = T"
515           STOP
516       ELSE
517           write(*,*) "mugaz=",mugaz
518       ENDIF
519       cpp = -99999.
520       PRINT *,'SPECIFIC HEAT CAPACITY in J K-1 kg-1 ?'
521       call getin_p("cpp",cpp)
522       IF (cpp.eq.-99999.) THEN
523           PRINT *, "cpp must be set if force_cpp = T"
524           STOP
525       ELSE
526           write(*,*) "cpp=",cpp
527       ENDIF
528!         else
529!           mugaz=8.314*1000./pr
530     endif ! of if (force_cpp)
531     
532     
533     call su_gases(nlayer,tracer)     
534     call calc_cpp_mugaz
535     
536     
537     PRINT*,'--------------------------------------------'
538     PRINT*
539     PRINT*
540  ELSE
541     write(*,*)
542     write(*,*) 'Cannot read file callphys.def. Is it here ?'
543     stop
544  ENDIF ! of IF(iscallphys)
545
546  PRINT*
547  PRINT*,'inifis: daysec',daysec
548  PRINT*
549  PRINT*,'inifis: The radiative transfer is computed:'
550  PRINT*,'           each ',iradia,' physical time-step'
551  PRINT*,'        or each ',iradia*dtphys,' seconds'
552  PRINT*
553  PRINT*,'inifis: Chemistry is computed:'
554  PRINT*,'           each ',ichim,' physical time-step'
555  PRINT*,'        or each ',ichim*dtphys,' seconds'
556  PRINT*
557
558!-----------------------------------------------------------------------
559!     Some more initialization:
560!     ------------------------
561
562  ! Initializations for comgeomfi_h
563  totarea=SSUM(ngrid,parea,1)
564  call planetwide_sumval(parea,totarea_planet)
565
566  !! those are defined in comdiurn_h.F90
567  IF (.not.ALLOCATED(sinlat)) ALLOCATE(sinlat(ngrid))
568  IF (.not.ALLOCATED(coslat)) ALLOCATE(coslat(ngrid))
569  IF (.not.ALLOCATED(sinlon)) ALLOCATE(sinlon(ngrid))
570  IF (.not.ALLOCATED(coslon)) ALLOCATE(coslon(ngrid))
571
572  DO ig=1,ngrid
573     sinlat(ig)=sin(plat(ig))
574     coslat(ig)=cos(plat(ig))
575     sinlon(ig)=sin(plon(ig))
576     coslon(ig)=cos(plon(ig))
577  ENDDO
578
579  ! initialize variables in radinc_h
580  call ini_radinc_h(nlayer)
581 
582  ! allocate "comsoil_h" arrays
583  call ini_comsoil_h(ngrid)
584     
585  END SUBROUTINE inifis
586
587END MODULE inifis_mod
Note: See TracBrowser for help on using the repository browser.