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

Last change on this file since 601 was 596, checked in by jleconte, 13 years ago
  • Added double gray case (if graybody=true in callphys.def):
    • opacities are set to a constant value in sugas_corrk.
    • the values are kappa_IR m2/kg in the infrared (to be read in callphys.def)

kappa_VI m2/kg in the visible (to be read in callphys.def)

  • Cleaned continuum part in optc*
  • Added .def files for a typical 1d earth case in deftank (dry case for the moment)
File size: 18.3 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 
207         write(*,*) "call turbulent vertical diffusion ?"
208         calldifv=.true. ! default value
209         call getin("calldifv",calldifv)
210         write(*,*) " calldifv = ",calldifv
211
212         write(*,*) "use turbdiff instead of vdifc ?"
213         UseTurbDiff=.true. ! default value
214         call getin("UseTurbDiff",UseTurbDiff)
215         write(*,*) " UseTurbDiff = ",UseTurbDiff
216
217         write(*,*) "call convective adjustment ?"
218         calladj=.true. ! default value
219         call getin("calladj",calladj)
220         write(*,*) " calladj = ",calladj
221       
222
223! Test of incompatibility
224         if (enertest.and.nonideal) then
225            print*,'Energy conservation calculations currently
226     &           assume ideal gas!'
227            call abort
228         endif
229
230         write(*,*) "call CO2 condensation ?"
231         co2cond=.true. ! default value
232         call getin("co2cond",co2cond)
233         write(*,*) " co2cond = ",co2cond
234
235         write(*,*) "CO2 supersaturation level ?"
236         co2supsat=1.0 ! default value
237         call getin("co2supsat",co2supsat)
238         write(*,*) " co2supsat = ",co2supsat
239
240         write(*,*) "Radiative timescale for Newtonian cooling ?"
241         tau_relax=30. ! default value
242         call getin("tau_relax",tau_relax)
243         write(*,*) " tau_relax = ",tau_relax
244         tau_relax=tau_relax*24*3600 ! convert Earth days --> seconds
245
246         write(*,*)"call thermal conduction in the soil ?"
247         callsoil=.true. ! default value
248         call getin("callsoil",callsoil)
249         write(*,*) " callsoil = ",callsoil
250         
251         write(*,*)"Rad transfer is computed every iradia",
252     &             " physical timestep"
253         iradia=1 ! default value
254         call getin("iradia",iradia)
255         write(*,*)" iradia = ",iradia
256       
257         write(*,*)"Rayleigh scattering ?"
258         rayleigh=.false.
259         call getin("rayleigh",rayleigh)
260         write(*,*)" rayleigh = ",rayleigh
261
262         write(*,*) "Use blackbody for stellar spectrum ?"
263         stelbbody=.false. ! default value
264         call getin("stelbbody",stelbbody)
265         write(*,*) " stelbbody = ",stelbbody
266
267         write(*,*) "Stellar blackbody temperature ?"
268         stelTbb=5800.0 ! default value
269         call getin("stelTbb",stelTbb)
270         write(*,*) " stelTbb = ",stelTbb
271
272         write(*,*)"Output mean OLR in 1D?"
273         meanOLR=.false.
274         call getin("meanOLR",meanOLR)
275         write(*,*)" meanOLR = ",meanOLR
276
277         write(*,*)"Output spectral OLR in 3D?"
278         specOLR=.false.
279         call getin("specOLR",specOLR)
280         write(*,*)" specOLR = ",specOLR
281
282         write(*,*)"Operate in kastprof mode?"
283         kastprof=.false.
284         call getin("kastprof",kastprof)
285         write(*,*)" kastprof = ",kastprof
286
287         write(*,*)"Uniform absorption in radiative transfer?"
288         graybody=.false.
289         call getin("graybody",graybody)
290         write(*,*)" graybody = ",graybody
291
292! Test of incompatibility:
293! if kastprof used, we must be in 1D
294         if (kastprof.and.(ngridmx.gt.1)) then
295           print*,'kastprof can only be used in 1D!'
296           call abort
297         endif
298
299         write(*,*)"Stratospheric temperature for kastprof mode?"
300         Tstrat=167.0
301         call getin("Tstrat",Tstrat)
302         write(*,*)" Tstrat = ",Tstrat
303
304         write(*,*)"Remove lower boundary?"
305         noradsurf=.false.
306         call getin("noradsurf",noradsurf)
307         write(*,*)" noradsurf = ",noradsurf
308
309! Tests of incompatibility:
310         if (noradsurf.and.callsoil) then
311           print*,'noradsurf not compatible with soil scheme!'
312           call abort
313         endif
314         !if (noradsurf.and.calldifv) then
315         !  print*,'noradsurf not compatible with a boundary layer!'
316         !  call abort
317         !endif
318
319         write(*,*)"Use Newtonian cooling for radiative transfer?"
320         newtonian=.false.
321         call getin("newtonian",newtonian)
322         write(*,*)" newtonian = ",newtonian
323
324! Tests of incompatibility:
325         if (newtonian.and.corrk) then
326           print*,'newtonian not compatible with correlated-k!'
327           call abort
328         endif
329         if (newtonian.and.calladj) then
330           print*,'newtonian not compatible with adjustment!'
331           call abort
332         endif
333         if (newtonian.and.calldifv) then
334           print*,'newtonian not compatible with a boundary layer!'
335           call abort
336         endif
337
338         write(*,*)"Test physics timescale in 1D?"
339         testradtimes=.false.
340         call getin("testradtimes",testradtimes)
341         write(*,*)" testradtimes = ",testradtimes
342
343! Test of incompatibility:
344! if testradtimes used, we must be in 1D
345         if (testradtimes.and.(ngridmx.gt.1)) then
346           print*,'testradtimes can only be used in 1D!'
347           call abort
348         endif
349
350         write(*,*)"Default planetary temperature?"
351         tplanet=215.0
352         call getin("tplanet",tplanet)
353         write(*,*)" tplanet = ",tplanet
354
355         write(*,*)"Which star?"
356         startype=1 ! default value = Sol
357         call getin("startype",startype)
358         write(*,*)" startype = ",startype
359
360         write(*,*)"Value of stellar flux at 1 AU?"
361         Fat1AU=1356.0 ! default value = Sol today
362         call getin("Fat1AU",Fat1AU)
363         write(*,*)" Fat1AU = ",Fat1AU
364
365
366! TRACERS:
367
368         write(*,*)"Fixed / inactive aerosol distribution?"
369         aerofixed=.true.       ! default value
370         call getin("aerofixed",aerofixed)
371         write(*,*)" aerofixed = ",aerofixed
372
373         write(*,*)"Varying H2O cloud fraction?"
374         CLFvarying=.false.     ! default value
375         call getin("CLFvarying",CLFvarying)
376         write(*,*)" CLFvarying = ",CLFvarying
377
378         write(*,*)"Value of fixed H2O cloud fraction?"
379         CLFfixval=1.0                ! default value
380         call getin("CLFfixval",CLFfixval)
381         write(*,*)" CLFfixval = ",CLFfixval
382
383         write(*,*)"Number mixing ratio of CO2 ice particles:"
384         Nmix_co2=100000. ! default value
385         call getin("Nmix_co2",Nmix_co2)
386         write(*,*)" Nmix_co2 = ",Nmix_co2
387
388         write(*,*)"Number mixing ratio of H2O ice particles:"
389         Nmix_h2o=10000000. ! default value
390         call getin("Nmix_h2o",Nmix_h2o)
391         write(*,*)" Nmix_h2o = ",Nmix_h2o
392
393         write(*,*)"Opacity of dust (if used):"
394         dusttau=0. ! default value
395         call getin("dusttau",dusttau)
396         write(*,*)" dusttau = ",dusttau
397
398! Test of incompatibility:
399! if less than 3 aerosols, then dusttau should = 0
400         if ((naerkind.lt.3).and.dusttau.gt.0.) then
401           print*,'Need naer>2 for radiatively active dust!'
402           stop
403         endif
404
405         write(*,*)"Cloud pressure level (with kastprof only):"
406         cloudlvl=0. ! default value
407         call getin("cloudlvl",cloudlvl)
408         write(*,*)" cloudlvl = ",cloudlvl
409
410         write(*,*)"Is the variable gas species radiatively active?"
411         Tstrat=167.0
412         varactive=.false.
413         call getin("varactive",varactive)
414         write(*,*)" varactive = ",varactive
415
416         write(*,*)"Is the variable gas species distribution set?"
417         varfixed=.false.
418         call getin("varfixed",varfixed)
419         write(*,*)" varfixed = ",varfixed
420
421         write(*,*)"What is the saturation % of the variable species?"
422         satval=0.8
423         call getin("satval",satval)
424         write(*,*)" satval = ",satval
425
426! Test of incompatibility:
427! if no tracers, then aerofixed should be true
428         if ((.not.tracer).and.(.not.aerofixed)) then
429           print*,'if tracers are off, aerofixed must be ON!'
430           stop
431         endif
432
433! Test of incompatibility:
434! if varactive, then varfixed should be false
435         if (varactive.and.varfixed) then
436           print*,'if varactive, varfixed must be OFF!'
437           stop
438         endif
439
440! Test of incompatibility:
441
442         write(*,*) "Gravitationnal sedimentation ?"
443         sedimentation=.true. ! default value
444         call getin("sedimentation",sedimentation)
445         write(*,*) " sedimentation = ",sedimentation
446
447
448! Test of incompatibility:
449
450         write(*,*) "Compute water cycle ?"
451         water=.false. ! default value
452         call getin("water",water)
453         write(*,*) " water = ",water
454         
455         write(*,*) "Include water condensation ?"
456         watercond=.false. ! default value
457         call getin("watercond",watercond)
458         write(*,*) " watercond = ",watercond
459
460         write(*,*) "Include water precipitation ?"
461         waterrain=.false. ! default value
462         call getin("waterrain",waterrain)
463         write(*,*) " waterrain = ",waterrain
464
465         write(*,*) "Precipitation threshold ?"
466         rainthreshold=0.011 ! default value (Emmanuel 1997)
467         call getin("rainthreshold",rainthreshold)
468         write(*,*) " rainthreshold = ",rainthreshold
469
470         write(*,*) "Include surface hydrology ?"
471         hydrology=.false. ! default value
472         call getin("hydrology",hydrology)
473         write(*,*) " hydrology = ",hydrology
474
475         write(*,*) "Evolve surface water sources ?"
476         sourceevol=.false. ! default value
477         call getin("sourceevol",sourceevol)
478         write(*,*) " sourceevol = ",sourceevol
479
480         write(*,*) "Ice evolution timestep ?"
481         icetstep=100.0 ! default value
482         call getin("icetstep",icetstep)
483         write(*,*) " icetstep = ",icetstep
484
485         write(*,*) "Snow albedo ?"
486         albedosnow=0.5         ! default value
487         call getin("albedosnow",albedosnow)
488         write(*,*) " albedosnow = ",albedosnow
489
490         write(*,*) "Maximum ice thickness ?"
491         maxicethick=2.0         ! default value
492         call getin("maxicethick",maxicethick)
493         write(*,*) " maxicethick = ",maxicethick
494
495         write(*,*) "Freezing point of seawater ?"
496         Tsaldiff=-1.8          ! default value
497         call getin("Tsaldiff",Tsaldiff)
498         write(*,*) " Tsaldiff = ",Tsaldiff
499
500! Test of incompatibility:
501! if watercond is used, then water should be used too
502
503         if (watercond.and.(.not.watercond)) then
504           print*,'if watercond is used, water should be used too'
505           stop
506         endif
507
508         write(*,*) "Does user want to force cpp and mugaz?"
509         force_cpp=.false. ! default value
510         call getin("force_cpp",force_cpp)
511         write(*,*) " force_cpp = ",force_cpp
512
513         if (force_cpp) then
514           mugaz = -99999.
515           PRINT *,'MEAN MOLECULAR MASS in g mol-1 ?'
516           call getin("mugaz",mugaz)
517           IF (mugaz.eq.-99999.) THEN
518               PRINT *, "mugaz must be set if force_cpp = T"
519               STOP
520           ELSE
521               write(*,*) "mugaz=",mugaz
522           ENDIF
523           cpp = -99999.
524           PRINT *,'SPECIFIC HEAT CAPACITY in J K-1 kg-1 ?'
525           call getin("cpp",cpp)
526           IF (cpp.eq.-99999.) THEN
527               PRINT *, "cpp must be set if force_cpp = T"
528               STOP
529           ELSE
530               write(*,*) "cpp=",cpp
531           ENDIF
532         else
533           mugaz=8.314*1000./pr
534         endif
535         call su_gases
536         call calc_cpp_mugaz
537
538         PRINT*,'--------------------------------------------'
539         PRINT*
540         PRINT*
541      ELSE
542         write(*,*)
543         write(*,*) 'Cannot read file callphys.def. Is it here ?'
544         stop
545      ENDIF
546
5478000  FORMAT(t5,a12,l8)
5488001  FORMAT(t5,a12,i8)
549
550      PRINT*
551      PRINT*,'inifis: daysec',daysec
552      PRINT*
553      PRINT*,'inifis: The radiative transfer is computed:'
554      PRINT*,'           each ',iradia,' physical time-step'
555      PRINT*,'        or each ',iradia*dtphys,' seconds'
556      PRINT*
557
558
559!-----------------------------------------------------------------------
560!     Some more initialization:
561!     ------------------------
562
563      CALL SCOPY(ngrid,plon,1,long,1)
564      CALL SCOPY(ngrid,plat,1,lati,1)
565      CALL SCOPY(ngrid,parea,1,area,1)
566      totarea=SSUM(ngridmx,area,1)
567
568      DO ig=1,ngrid
569         sinlat(ig)=sin(plat(ig))
570         coslat(ig)=cos(plat(ig))
571         sinlon(ig)=sin(plon(ig))
572         coslon(ig)=cos(plon(ig))
573      ENDDO
574
575      pi=2.*asin(1.) ! NB: pi is a common in comcstfi.h
576
577      RETURN
578      END
Note: See TracBrowser for help on using the repository browser.