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

Last change on this file since 344 was 305, checked in by rwordsworth, 14 years ago

Several new files added as part of the climate evolution model
(main program kcm.F90). Some general cleanup in physiq.F90 and
callcorrk.F90. Bugs in dust radiative transfer and H2 Rayleigh
scattering corrected.

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