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

Last change on this file since 304 was 253, checked in by emillour, 13 years ago

Generic GCM

  • Massive update to version 0.7

EM+RW

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