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

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

Some updates of the deftank and the default values in inifis_mod
--JVO

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