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

Last change on this file since 1896 was 1896, checked in by jvatant, 7 years ago

Merge EM modifs on phy_common and xios
from LMDZ.GENERIC to LMDZ.TITAN.
See logs from r1673, r1682 and r1760
--JVO

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