source: trunk/LMDZ.GENERIC/libf/phystd/inifis.F @ 724

Last change on this file since 724 was 716, checked in by rwordsworth, 13 years ago

Mainly updates to radiative transfer and gas management scheme.
Most CIA data now read from standard HITRAN datafiles. For the H2O
continuum, two options have been added: the standard CKD continuum,
and the empirical formula in PPC (Pierrehumbert 2010). Use the toggle
'H2Ocont_simple' in callphys.def to choose.

Note to Martians: I've changed the default values of 'sedimentation' and
'co2cond' in inifis to false. Both these are defined in the standard deftank
callphys.def file, so there shouldn't be any compatibility problems.

File size: 18.6 KB
Line 
1      SUBROUTINE inifis(ngrid,nlayer,
2     $           day_ini,pdaysec,ptimestep,
3     $           plat,plon,parea,
4     $           prad,pg,pr,pcpp)
5
6      use radinc_h, only : naerkind
7      use datafile_mod, only: datadir
8
9!=======================================================================
10!
11!   purpose:
12!   -------
13!
14!   Initialisation for the physical parametrisations of the LMD
15!   Generic Model.
16!
17!   author: Frederic Hourdin 15 / 10 /93
18!   -------
19!   modified: Sebastien Lebonnois 11/06/2003 (new callphys.def)
20!             Ehouarn Millour (oct. 2008) tracers are now identified
21!              by their names and may not be contiguously
22!              stored in the q(:,:,:,:) array
23!             E.M. (june 2009) use getin routine to load parameters
24!
25!
26!   arguments:
27!   ----------
28!
29!   input:
30!   ------
31!
32!    ngrid                 Size of the horizontal grid.
33!                          All internal loops are performed on that grid.
34!    nlayer                Number of vertical layers.
35!    pdayref               Day of reference for the simulation
36!    pday                  Number of days counted from the North. Spring
37!                          equinoxe.
38!
39!=======================================================================
40!
41!-----------------------------------------------------------------------
42!   declarations:
43!   -------------
44      use datafile_mod, only: datadir
45! to use  'getin'
46      USE ioipsl_getincom
47      IMPLICIT NONE
48#include "dimensions.h"
49#include "dimphys.h"
50#include "planete.h"
51#include "comcstfi.h"
52#include "comsaison.h"
53#include "comdiurn.h"
54#include "comgeomfi.h"
55#include "callkeys.h"
56#include "surfdat.h"
57
58
59
60      REAL prad,pg,pr,pcpp,pdaysec,ptimestep
61 
62      INTEGER ngrid,nlayer
63      REAL plat(ngrid),plon(ngrid),parea(ngridmx)
64      integer day_ini
65      INTEGER ig,ierr
66 
67      EXTERNAL iniorbit,orbite
68      EXTERNAL SSUM
69      REAL SSUM
70 
71      CHARACTER ch1*12
72      CHARACTER ch80*80
73
74      logical chem, h2o
75      logical :: parameter, doubleq=.false.
76
77      real psurf,pN2 ! added by RW for Gliese 581d N2+CO2
78
79      rad=prad
80      daysec=pdaysec
81      dtphys=ptimestep
82      cpp=pcpp
83      g=pg
84      r=pr
85      rcp=r/cpp
86
87      avocado = 6.02214179e23   ! added by RW
88
89! --------------------------------------------------------
90!     The usual Tests
91!     --------------
92      IF (nlayer.NE.nlayermx) THEN
93         PRINT*,'STOP in inifis'
94         PRINT*,'Probleme de dimensions :'
95         PRINT*,'nlayer     = ',nlayer
96         PRINT*,'nlayermx   = ',nlayermx
97         STOP
98      ENDIF
99
100      IF (ngrid.NE.ngridmx) THEN
101         PRINT*,'STOP in inifis'
102         PRINT*,'Probleme de dimensions :'
103         PRINT*,'ngrid     = ',ngrid
104         PRINT*,'ngridmx   = ',ngridmx
105         STOP
106      ENDIF
107
108! --------------------------------------------------------------
109!  Reading the "callphys.def" file controlling some key options
110! --------------------------------------------------------------
111     
112      ! check that 'callphys.def' file is around
113      OPEN(99,file='callphys.def',status='old',form='formatted'
114     &     ,iostat=ierr)
115      CLOSE(99)
116     
117      IF(ierr.EQ.0) THEN
118         PRINT*
119         PRINT*
120         PRINT*,'--------------------------------------------'
121         PRINT*,' inifis: Parametres pour la physique (callphys.def)'
122         PRINT*,'--------------------------------------------'
123
124         write(*,*) "Directory where external input files are:"
125         ! default 'datadir' is set in "datadir_mod"
126         call getin("datadir",datadir) ! default path
127         write(*,*) " datadir = ",trim(datadir)
128
129         write(*,*) "Run with or without tracer transport ?"
130         tracer=.false. ! default value
131         call getin("tracer",tracer)
132         write(*,*) " tracer = ",tracer
133
134         write(*,*) "Diurnal cycle ?"
135         write(*,*) "(if diurnal=false, diurnal averaged solar heating)"
136         diurnal=.true. ! default value
137         call getin("diurnal",diurnal)
138         write(*,*) " diurnal = ",diurnal
139
140         write(*,*) "Seasonal cycle ?"
141         write(*,*) "(if season=false, Ls stays constant, to value ",
142     &   "set in 'start'"
143         season=.true. ! default value
144         call getin("season",season)
145         write(*,*) " season = ",season
146
147         write(*,*) "Tidally resonant rotation ?"
148         tlocked=.false. ! default value
149         call getin("tlocked",tlocked)
150         write(*,*) "tlocked = ",tlocked
151
152! Test of incompatibility:
153! if tlocked, then diurnal should be false
154         if (tlocked.and.diurnal) then
155           print*,'If diurnal=true, we should turn off tlocked.'
156           stop
157         endif
158
159         write(*,*) "Tidal resonance ratio ?"
160         nres=0          ! default value
161         call getin("nres",nres)
162         write(*,*) "nres = ",nres
163
164         write(*,*) "Write some extra output to the screen ?"
165         lwrite=.false. ! default value
166         call getin("lwrite",lwrite)
167         write(*,*) " lwrite = ",lwrite
168
169         write(*,*) "Save statistics in file stats.nc ?"
170         callstats=.true. ! default value
171         call getin("callstats",callstats)
172         write(*,*) " callstats = ",callstats
173
174         write(*,*) "Test energy conservation of model physics ?"
175         enertest=.false. ! default value
176         call getin("enertest",enertest)
177         write(*,*) " enertest = ",enertest
178
179         write(*,*) "Check to see if cpp values used match gases.def ?"
180         check_cpp_match=.true. ! default value
181         call getin("check_cpp_match",check_cpp_match)
182         write(*,*) " check_cpp_match = ",check_cpp_match
183
184         write(*,*) "call radiative transfer ?"
185         callrad=.true. ! default value
186         call getin("callrad",callrad)
187         write(*,*) " callrad = ",callrad
188
189         write(*,*) "call correlated-k radiative transfer ?"
190         corrk=.true. ! default value
191         call getin("corrk",corrk)
192         write(*,*) " corrk = ",corrk
193
194         write(*,*) "call gaseous absorption in the visible bands?",
195     &              "(matters only if callrad=T)"
196         callgasvis=.false. ! default value
197         call getin("callgasvis",callgasvis)
198         write(*,*) " callgasvis = ",callgasvis
199       
200         write(*,*) "call continuum opacities in radiative transfer ?",
201     &              "(matters only if callrad=T)"
202         Continuum=.true. ! default value
203         call getin("Continuum",Continuum)
204         write(*,*) " Continuum = ",Continuum
205
206         write(*,*) "use analytic function for H2O continuum ?"
207         H2Ocont_simple=.false. ! default value
208         call getin("H2Ocont_simple",H2Ocont_simple)
209         write(*,*) " H2Ocont_simple = ",H2Ocont_simple
210 
211         write(*,*) "call turbulent vertical diffusion ?"
212         calldifv=.true. ! default value
213         call getin("calldifv",calldifv)
214         write(*,*) " calldifv = ",calldifv
215
216         write(*,*) "use turbdiff instead of vdifc ?"
217         UseTurbDiff=.true. ! default value
218         call getin("UseTurbDiff",UseTurbDiff)
219         write(*,*) " UseTurbDiff = ",UseTurbDiff
220
221         write(*,*) "call convective adjustment ?"
222         calladj=.true. ! default value
223         call getin("calladj",calladj)
224         write(*,*) " calladj = ",calladj
225
226         write(*,*) "call CO2 condensation ?"
227         co2cond=.false. ! default value
228         call getin("co2cond",co2cond)
229         write(*,*) " co2cond = ",co2cond
230! Test of incompatibility
231         if (co2cond.and.(.not.tracer)) then
232            print*,'We need a CO2 ice tracer to condense CO2'
233            call abort
234         endif
235 
236         write(*,*) "CO2 supersaturation level ?"
237         co2supsat=1.0 ! default value
238         call getin("co2supsat",co2supsat)
239         write(*,*) " co2supsat = ",co2supsat
240
241         write(*,*) "Radiative timescale for Newtonian cooling ?"
242         tau_relax=30. ! default value
243         call getin("tau_relax",tau_relax)
244         write(*,*) " tau_relax = ",tau_relax
245         tau_relax=tau_relax*24*3600 ! convert Earth days --> seconds
246
247         write(*,*)"call thermal conduction in the soil ?"
248         callsoil=.true. ! default value
249         call getin("callsoil",callsoil)
250         write(*,*) " callsoil = ",callsoil
251         
252         write(*,*)"Rad transfer is computed every iradia",
253     &             " physical timestep"
254         iradia=1 ! default value
255         call getin("iradia",iradia)
256         write(*,*)" iradia = ",iradia
257       
258         write(*,*)"Rayleigh scattering ?"
259         rayleigh=.false.
260         call getin("rayleigh",rayleigh)
261         write(*,*)" rayleigh = ",rayleigh
262
263         write(*,*) "Use blackbody for stellar spectrum ?"
264         stelbbody=.false. ! default value
265         call getin("stelbbody",stelbbody)
266         write(*,*) " stelbbody = ",stelbbody
267
268         write(*,*) "Stellar blackbody temperature ?"
269         stelTbb=5800.0 ! default value
270         call getin("stelTbb",stelTbb)
271         write(*,*) " stelTbb = ",stelTbb
272
273         write(*,*)"Output mean OLR in 1D?"
274         meanOLR=.false.
275         call getin("meanOLR",meanOLR)
276         write(*,*)" meanOLR = ",meanOLR
277
278         write(*,*)"Output spectral OLR in 3D?"
279         specOLR=.false.
280         call getin("specOLR",specOLR)
281         write(*,*)" specOLR = ",specOLR
282
283         write(*,*)"Operate in kastprof mode?"
284         kastprof=.false.
285         call getin("kastprof",kastprof)
286         write(*,*)" kastprof = ",kastprof
287
288         write(*,*)"Uniform absorption in radiative transfer?"
289         graybody=.false.
290         call getin("graybody",graybody)
291         write(*,*)" graybody = ",graybody
292
293! Test of incompatibility:
294! if kastprof used, we must be in 1D
295         if (kastprof.and.(ngridmx.gt.1)) then
296           print*,'kastprof can only be used in 1D!'
297           call abort
298         endif
299
300         write(*,*)"Stratospheric temperature for kastprof mode?"
301         Tstrat=167.0
302         call getin("Tstrat",Tstrat)
303         write(*,*)" Tstrat = ",Tstrat
304
305         write(*,*)"Remove lower boundary?"
306         noradsurf=.false.
307         call getin("noradsurf",noradsurf)
308         write(*,*)" noradsurf = ",noradsurf
309
310! Tests of incompatibility:
311         if (noradsurf.and.callsoil) then
312           print*,'noradsurf not compatible with soil scheme!'
313           call abort
314         endif
315         !if (noradsurf.and.calldifv) then
316         !  print*,'noradsurf not compatible with a boundary layer!'
317         !  call abort
318         !endif
319
320         write(*,*)"Use Newtonian cooling for radiative transfer?"
321         newtonian=.false.
322         call getin("newtonian",newtonian)
323         write(*,*)" newtonian = ",newtonian
324
325! Tests of incompatibility:
326         if (newtonian.and.corrk) then
327           print*,'newtonian not compatible with correlated-k!'
328           call abort
329         endif
330         if (newtonian.and.calladj) then
331           print*,'newtonian not compatible with adjustment!'
332           call abort
333         endif
334         if (newtonian.and.calldifv) then
335           print*,'newtonian not compatible with a boundary layer!'
336           call abort
337         endif
338
339         write(*,*)"Test physics timescale in 1D?"
340         testradtimes=.false.
341         call getin("testradtimes",testradtimes)
342         write(*,*)" testradtimes = ",testradtimes
343
344! Test of incompatibility:
345! if testradtimes used, we must be in 1D
346         if (testradtimes.and.(ngridmx.gt.1)) then
347           print*,'testradtimes can only be used in 1D!'
348           call abort
349         endif
350
351         write(*,*)"Default planetary temperature?"
352         tplanet=215.0
353         call getin("tplanet",tplanet)
354         write(*,*)" tplanet = ",tplanet
355
356         write(*,*)"Which star?"
357         startype=1 ! default value = Sol
358         call getin("startype",startype)
359         write(*,*)" startype = ",startype
360
361         write(*,*)"Value of stellar flux at 1 AU?"
362         Fat1AU=1356.0 ! default value = Sol today
363         call getin("Fat1AU",Fat1AU)
364         write(*,*)" Fat1AU = ",Fat1AU
365
366
367! TRACERS:
368
369         write(*,*)"Fixed / inactive aerosol distribution?"
370         aerofixed=.true.       ! default value
371         call getin("aerofixed",aerofixed)
372         write(*,*)" aerofixed = ",aerofixed
373
374         write(*,*)"Varying H2O cloud fraction?"
375         CLFvarying=.false.     ! default value
376         call getin("CLFvarying",CLFvarying)
377         write(*,*)" CLFvarying = ",CLFvarying
378
379         write(*,*)"Value of fixed H2O cloud fraction?"
380         CLFfixval=1.0                ! default value
381         call getin("CLFfixval",CLFfixval)
382         write(*,*)" CLFfixval = ",CLFfixval
383
384         write(*,*)"Number mixing ratio of CO2 ice particles:"
385         Nmix_co2=100000. ! default value
386         call getin("Nmix_co2",Nmix_co2)
387         write(*,*)" Nmix_co2 = ",Nmix_co2
388
389         write(*,*)"Number mixing ratio of H2O ice particles:"
390         Nmix_h2o=10000000. ! default value
391         call getin("Nmix_h2o",Nmix_h2o)
392         write(*,*)" Nmix_h2o = ",Nmix_h2o
393
394         write(*,*)"Opacity of dust (if used):"
395         dusttau=0. ! default value
396         call getin("dusttau",dusttau)
397         write(*,*)" dusttau = ",dusttau
398
399! Test of incompatibility:
400! if less than 3 aerosols, then dusttau should = 0
401         if ((naerkind.lt.3).and.dusttau.gt.0.) then
402           print*,'Need naer>2 for radiatively active dust!'
403           stop
404         endif
405
406         write(*,*)"Cloud pressure level (with kastprof only):"
407         cloudlvl=0. ! default value
408         call getin("cloudlvl",cloudlvl)
409         write(*,*)" cloudlvl = ",cloudlvl
410
411         write(*,*)"Is the variable gas species radiatively active?"
412         Tstrat=167.0
413         varactive=.false.
414         call getin("varactive",varactive)
415         write(*,*)" varactive = ",varactive
416
417         write(*,*)"Is the variable gas species distribution set?"
418         varfixed=.false.
419         call getin("varfixed",varfixed)
420         write(*,*)" varfixed = ",varfixed
421
422         write(*,*)"What is the saturation % of the variable species?"
423         satval=0.8
424         call getin("satval",satval)
425         write(*,*)" satval = ",satval
426
427! Test of incompatibility:
428! if no tracers, then aerofixed should be true
429         if ((.not.tracer).and.(.not.aerofixed)) then
430           print*,'if tracers are off, aerofixed must be ON!'
431           stop
432         endif
433
434! Test of incompatibility:
435! if varactive, then varfixed should be false
436         if (varactive.and.varfixed) then
437           print*,'if varactive, varfixed must be OFF!'
438           stop
439         endif
440
441         write(*,*) "Gravitationnal sedimentation ?"
442         sedimentation=.false. ! default value
443         call getin("sedimentation",sedimentation)
444         write(*,*) " sedimentation = ",sedimentation
445
446         write(*,*) "Compute water cycle ?"
447         water=.false. ! default value
448         call getin("water",water)
449         write(*,*) " water = ",water
450         
451! Test of incompatibility:
452! if water is true, there should be at least a tracer
453         if (water.and.(.not.tracer)) then
454           print*,'if water is ON, tracer must be ON too!'
455           stop
456         endif
457
458         write(*,*) "Include water condensation ?"
459         watercond=.false. ! default value
460         call getin("watercond",watercond)
461         write(*,*) " watercond = ",watercond
462
463! Test of incompatibility:
464! if watercond is used, then water should be used too
465         if (watercond.and.(.not.water)) then
466           print*,'if watercond is used, water should be used too'
467           stop
468         endif
469
470         write(*,*) "Include water precipitation ?"
471         waterrain=.false. ! default value
472         call getin("waterrain",waterrain)
473         write(*,*) " waterrain = ",waterrain
474
475         write(*,*) "Precipitation threshold ?"
476         rainthreshold=0.011 ! default value (Emmanuel 1997)
477         call getin("rainthreshold",rainthreshold)
478         write(*,*) " rainthreshold = ",rainthreshold
479
480         write(*,*) "Include surface hydrology ?"
481         hydrology=.false. ! default value
482         call getin("hydrology",hydrology)
483         write(*,*) " hydrology = ",hydrology
484
485         write(*,*) "Evolve surface water sources ?"
486         sourceevol=.false. ! default value
487         call getin("sourceevol",sourceevol)
488         write(*,*) " sourceevol = ",sourceevol
489
490         write(*,*) "Ice evolution timestep ?"
491         icetstep=100.0 ! default value
492         call getin("icetstep",icetstep)
493         write(*,*) " icetstep = ",icetstep
494
495         write(*,*) "Snow albedo ?"
496         albedosnow=0.5         ! default value
497         call getin("albedosnow",albedosnow)
498         write(*,*) " albedosnow = ",albedosnow
499
500         write(*,*) "Maximum ice thickness ?"
501         maxicethick=2.0         ! default value
502         call getin("maxicethick",maxicethick)
503         write(*,*) " maxicethick = ",maxicethick
504
505         write(*,*) "Freezing point of seawater ?"
506         Tsaldiff=-1.8          ! default value
507         call getin("Tsaldiff",Tsaldiff)
508         write(*,*) " Tsaldiff = ",Tsaldiff
509
510         write(*,*) "Does user want to force cpp and mugaz?"
511         force_cpp=.false. ! default value
512         call getin("force_cpp",force_cpp)
513         write(*,*) " force_cpp = ",force_cpp
514
515         if (force_cpp) then
516           mugaz = -99999.
517           PRINT *,'MEAN MOLECULAR MASS in g mol-1 ?'
518           call getin("mugaz",mugaz)
519           IF (mugaz.eq.-99999.) THEN
520               PRINT *, "mugaz must be set if force_cpp = T"
521               STOP
522           ELSE
523               write(*,*) "mugaz=",mugaz
524           ENDIF
525           cpp = -99999.
526           PRINT *,'SPECIFIC HEAT CAPACITY in J K-1 kg-1 ?'
527           call getin("cpp",cpp)
528           IF (cpp.eq.-99999.) THEN
529               PRINT *, "cpp must be set if force_cpp = T"
530               STOP
531           ELSE
532               write(*,*) "cpp=",cpp
533           ENDIF
534         else
535           mugaz=8.314*1000./pr
536         endif
537         call su_gases
538         call calc_cpp_mugaz
539
540         PRINT*,'--------------------------------------------'
541         PRINT*
542         PRINT*
543      ELSE
544         write(*,*)
545         write(*,*) 'Cannot read file callphys.def. Is it here ?'
546         stop
547      ENDIF
548
5498000  FORMAT(t5,a12,l8)
5508001  FORMAT(t5,a12,i8)
551
552      PRINT*
553      PRINT*,'inifis: daysec',daysec
554      PRINT*
555      PRINT*,'inifis: The radiative transfer is computed:'
556      PRINT*,'           each ',iradia,' physical time-step'
557      PRINT*,'        or each ',iradia*dtphys,' seconds'
558      PRINT*
559
560
561!-----------------------------------------------------------------------
562!     Some more initialization:
563!     ------------------------
564
565      CALL SCOPY(ngrid,plon,1,long,1)
566      CALL SCOPY(ngrid,plat,1,lati,1)
567      CALL SCOPY(ngrid,parea,1,area,1)
568      totarea=SSUM(ngridmx,area,1)
569
570      DO ig=1,ngrid
571         sinlat(ig)=sin(plat(ig))
572         coslat(ig)=cos(plat(ig))
573         sinlon(ig)=sin(plon(ig))
574         coslon(ig)=cos(plon(ig))
575      ENDDO
576
577      pi=2.*asin(1.) ! NB: pi is a common in comcstfi.h
578
579      RETURN
580      END
Note: See TracBrowser for help on using the repository browser.