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

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

+ Add diagnostics of optical thickness, in 1D, if 'diagdtau' key is activated, it

outputs dtaui/v(altitude) in diagfi.nc for every narrowband (could be done with one var
but would require to be able to have writediag in 5D

--JVO

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