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

Last change on this file since 580 was 538, checked in by rwordsworth, 13 years ago

calc_cpp_mugaz changed to a check only in 3D

File size: 17.5 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         write(*,*)"Gas is nonideal CO2 ?"
219         nonideal=.false.
220         call getin("nonideal",nonideal)
221         write(*,*)" nonideal = ",nonideal
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 coefficient in IR?"
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!     1D solar zenith angle
367         write(*,*)"Solar zenith angle in 1D?"
368         szangle=60.0
369         call getin("szangle",szangle)
370         write(*,*)" szangle = ",szangle
371
372! TRACERS:
373
374         write(*,*)"Fixed / inactive aerosol distribution?"
375         aerofixed=.true.       ! default value
376         call getin("aerofixed",aerofixed)
377         write(*,*)" aerofixed = ",aerofixed
378
379         write(*,*)"Varying H2O cloud fraction?"
380         CLFvarying=.false.     ! default value
381         call getin("CLFvarying",CLFvarying)
382         write(*,*)" CLFvarying = ",CLFvarying
383
384         write(*,*)"Value of fixed H2O cloud fraction?"
385         CLFfixval=1.0                ! default value
386         call getin("CLFfixval",CLFfixval)
387         write(*,*)" CLFfixval = ",CLFfixval
388
389         write(*,*)"Number mixing ratio of CO2 ice particles:"
390         Nmix_co2=100000. ! default value
391         call getin("Nmix_co2",Nmix_co2)
392         write(*,*)" Nmix_co2 = ",Nmix_co2
393
394         write(*,*)"Number mixing ratio of H2O ice particles:"
395         Nmix_h2o=10000000. ! default value
396         call getin("Nmix_h2o",Nmix_h2o)
397         write(*,*)" Nmix_h2o = ",Nmix_h2o
398
399         write(*,*)"Opacity of dust (if used):"
400         dusttau=0. ! default value
401         call getin("dusttau",dusttau)
402         write(*,*)" dusttau = ",dusttau
403
404! Test of incompatibility:
405! if less than 3 aerosols, then dusttau should = 0
406         if ((naerkind.lt.3).and.dusttau.gt.0.) then
407           print*,'Need naer>2 for radiatively active dust!'
408           stop
409         endif
410
411         write(*,*)"Cloud pressure level (with kastprof only):"
412         cloudlvl=0. ! default value
413         call getin("cloudlvl",cloudlvl)
414         write(*,*)" cloudlvl = ",cloudlvl
415
416         write(*,*)"Is the variable gas species radiatively active?"
417         Tstrat=167.0
418         varactive=.false.
419         call getin("varactive",varactive)
420         write(*,*)" varactive = ",varactive
421
422         write(*,*)"Is the variable gas species distribution set?"
423         varfixed=.false.
424         call getin("varfixed",varfixed)
425         write(*,*)" varfixed = ",varfixed
426
427         write(*,*)"What is the saturation % of the variable species?"
428         satval=0.8
429         call getin("satval",satval)
430         write(*,*)" satval = ",satval
431
432! Test of incompatibility:
433! if no tracers, then aerofixed should be true
434         if ((.not.tracer).and.(.not.aerofixed)) then
435           print*,'if tracers are off, aerofixed must be ON!'
436           stop
437         endif
438
439! Test of incompatibility:
440! if varactive, then varfixed should be false
441         if (varactive.and.varfixed) then
442           print*,'if varactive, varfixed must be OFF!'
443           stop
444         endif
445
446! Test of incompatibility:
447
448         write(*,*) "Gravitationnal sedimentation ?"
449         sedimentation=.true. ! default value
450         call getin("sedimentation",sedimentation)
451         write(*,*) " sedimentation = ",sedimentation
452
453
454! Test of incompatibility:
455
456         write(*,*) "Compute water cycle ?"
457         water=.false. ! default value
458         call getin("water",water)
459         write(*,*) " water = ",water
460         
461         write(*,*) "Include water condensation ?"
462         watercond=.false. ! default value
463         call getin("watercond",watercond)
464         write(*,*) " watercond = ",watercond
465
466         write(*,*) "Include water precipitation ?"
467         waterrain=.false. ! default value
468         call getin("waterrain",waterrain)
469         write(*,*) " waterrain = ",waterrain
470
471         write(*,*) "Precipitation threshold ?"
472         rainthreshold=0.011 ! default value (Emmanuel 1997)
473         call getin("rainthreshold",rainthreshold)
474         write(*,*) " rainthreshold = ",rainthreshold
475
476         write(*,*) "Include surface hydrology ?"
477         hydrology=.false. ! default value
478         call getin("hydrology",hydrology)
479         write(*,*) " hydrology = ",hydrology
480
481         write(*,*) "Evolve surface water sources ?"
482         sourceevol=.false. ! default value
483         call getin("sourceevol",sourceevol)
484         write(*,*) " sourceevol = ",sourceevol
485
486         write(*,*) "Ice evolution timestep ?"
487         icetstep=100.0 ! default value
488         call getin("icetstep",icetstep)
489         write(*,*) " icetstep = ",icetstep
490
491         write(*,*) "Snow albedo ?"
492         albedosnow=0.5         ! default value
493         call getin("albedosnow",albedosnow)
494         write(*,*) " albedosnow = ",albedosnow
495
496         write(*,*) "Maximum ice thickness ?"
497         maxicethick=2.0         ! default value
498         call getin("maxicethick",maxicethick)
499         write(*,*) " maxicethick = ",maxicethick
500
501         write(*,*) "Freezing point of seawater ?"
502         Tsaldiff=-1.8          ! default value
503         call getin("Tsaldiff",Tsaldiff)
504         write(*,*) " Tsaldiff = ",Tsaldiff
505
506! Test of incompatibility:
507! if watercond is used, then water should be used too
508
509         if (watercond.and.(.not.watercond)) then
510           print*,'if watercond is used, water should be used too'
511           stop
512         endif
513
514         mugaz=8.314*1000./pr
515         call su_gases
516         call calc_cpp_mugaz
517
518         PRINT*,'--------------------------------------------'
519         PRINT*
520         PRINT*
521      ELSE
522         write(*,*)
523         write(*,*) 'Cannot read file callphys.def. Is it here ?'
524         stop
525      ENDIF
526
5278000  FORMAT(t5,a12,l8)
5288001  FORMAT(t5,a12,i8)
529
530      PRINT*
531      PRINT*,'inifis: daysec',daysec
532      PRINT*
533      PRINT*,'inifis: The radiative transfer is computed:'
534      PRINT*,'           each ',iradia,' physical time-step'
535      PRINT*,'        or each ',iradia*dtphys,' seconds'
536      PRINT*
537
538
539!-----------------------------------------------------------------------
540!     Some more initialization:
541!     ------------------------
542
543      CALL SCOPY(ngrid,plon,1,long,1)
544      CALL SCOPY(ngrid,plat,1,lati,1)
545      CALL SCOPY(ngrid,parea,1,area,1)
546      totarea=SSUM(ngridmx,area,1)
547
548      DO ig=1,ngrid
549         sinlat(ig)=sin(plat(ig))
550         coslat(ig)=cos(plat(ig))
551         sinlon(ig)=sin(plon(ig))
552         coslon(ig)=cos(plon(ig))
553      ENDDO
554
555      pi=2.*asin(1.) ! NB: pi is a common in comcstfi.h
556
557      RETURN
558      END
Note: See TracBrowser for help on using the repository browser.