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

Last change on this file since 594 was 590, checked in by aslmd, 13 years ago

LMDZ.GENERIC: Introduced global1d in callcorrk so that global (using sza) or local (using latitude) 1D simulations can be carried out. Converted all astronomical distances in AU instead of Mkm. This might cause problems with old start files. So added a test in iniorbit. A quite dirty test, but thatll do the job.

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