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

Last change on this file since 588 was 586, checked in by jleconte, 13 years ago

removed cpp3D and nonideal stuff.

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