source: trunk/LMDZ.PLUTO.old/libf/phypluto/inifis.F @ 3232

Last change on this file since 3232 was 3175, checked in by emillour, 2 years ago

Pluto PCM:
Add the old Pluto LMDZ for reference (required prior step to making
an LMDZ.PLUTO using the same framework as the other physics packages).
TB+EM

File size: 31.6 KB
Line 
1      SUBROUTINE inifis(ngrid,nlayer,
2     $           day_ini,pdaysec,ptimestep,
3     $           plat,plon,parea,
4     $           prad,pg,pr,pcpp)
5!
6!=======================================================================
7!
8!   purpose:
9!   -------
10!
11!   Initialisation for the physical parametrisations of the LMD
12!   Pluto atmospheric general circulation modele.
13!   used by 1D Model only
14!
15!   author: Frederic Hourdin 15 / 10 /93
16!   -------
17!   modified: Sebastien Lebonnois 11/06/2003 (new callphys.def)
18!             Ehouarn Millour (oct. 2008) tracers are now identified
19!              by their names and may not be contiguously
20!              stored in the q(:,:,:,:) array
21!             E.M. (june 2009) use getin routine to load parameters
22!
23!
24!   arguments:
25!   ----------
26!
27!   input:
28!   ------
29!
30!    ngrid                 Size of the horizontal grid.
31!                          All internal loops are performed on that grid.
32!    nlayer                Number of vertical layers.
33!    pdayref               Day of reference for the simulation
34!    pday                  Number of days counted from the North. Spring
35!                          equinoxe.
36!
37!=======================================================================
38!
39!-----------------------------------------------------------------------
40!   declarations:
41!   -------------
42! to use  'getin'
43      USE ioipsl_getincom
44      use planet_h         
45      use comgeomfi_h
46      use datafile_mod
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 "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      rad=prad
76      daysec=pdaysec
77      dtphys=ptimestep
78      cpp=pcpp
79      g=pg
80      r=pr
81      rcp=r/cpp
82
83
84      avocado = 6.02214179e23   ! added by RW
85
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!***************************************************************
123         !! Directories / Files
124
125         write(*,*) "Directory where external input files are:"
126         datadir="../../../datagcm"  ! default path
127         call getin("datadir",datadir)
128         write(*,*) " datafile = ",trim(datadir)
129
130         write(*,*) "Haze optical properties datafile"
131         hazeprop="../../../datagcm"  ! default path
132         call getin("hazeprop",hazeprop)
133         write(*,*) " hazeprop = ",trim(hazeprop)
134
135!***************************************************************
136         !! Basics
137
138         write(*,*) "Run with or without tracer transport ?"
139         tracer=.false. ! default value
140         call getin("tracer",tracer)
141         write(*,*) " tracer = ",tracer
142
143         write(*,*) "Diurnal cycle ?"
144         write(*,*) "(if diurnal=false, diurnal averaged solar heating)"
145         diurnal=.true. ! default value
146         call getin("diurnal",diurnal)
147         write(*,*) " diurnal = ",diurnal
148
149         write(*,*) "Seasonal cycle ?"
150         write(*,*) "(if season=false, Ls stays constant, to value ",
151     &   "set in 'start'"
152         season=.true. ! default value
153         call getin("season",season)
154         write(*,*) " season = ",season
155
156         write(*,*) "Run 1D or 3D version (false) / fast version
157     &          volatile transport (true) ?"
158         fast=.false. ! default value
159         call getin("fast",fast)
160         write(*,*) " fast = ",fast
161
162         write(*,*) "1D options:"
163         globmean1d=.false. ! default value
164         call getin("globmean1d",globmean1d)
165         write(*,*) " globmean1d = ",globmean1d
166         kmixmin=1 ! default value
167         call getin("kmixmin",kmixmin)
168         write(*,*) " kmixmin = ",kmixmin
169         kmix_proffix=.false. ! default value
170         call getin("kmix_proffix",kmix_proffix)
171         write(*,*) " kmix_proffix = ",kmix_proffix
172
173         write(*,*) "Write some extra output to the screen ?"
174         lwrite=.false. ! default value
175         call getin("lwrite",lwrite)
176         write(*,*) " lwrite = ",lwrite
177
178         write(*,*) "Save statistics in file stats.nc ?"
179         callstats=.true. ! default value
180         call getin("callstats",callstats)
181         write(*,*) " callstats = ",callstats
182
183         write(*,*) "Test energy conservation of model physics ?"
184         enertest=.false. ! default value
185         call getin("enertest",enertest)
186         write(*,*) " enertest = ",enertest
187         conservn2=.false. ! default value
188         call getin("conservn2",conservn2)
189         write(*,*) " conservn2 = ",conservn2
190
191         write(*,*) "Run with Triton orbit ?"
192         triton=.false. ! default value
193         call getin("triton",triton)
194         write(*,*) " triton = ",triton
195         convergeps=.false. ! default value
196         call getin("convergeps",convergeps)
197         write(*,*) " convergeps = ",convergeps
198
199         write(*,*) "KBO runs (eris, makemake) ?"
200         kbo=.false. ! default value
201         call getin("kbo",kbo)
202         write(*,*) " kbo = ",kbo
203
204         write(*,*) "Specific paleo run ?"
205         paleo=.false. ! default value
206         call getin("paleo",paleo)
207         write(*,*) " paleo = ",paleo
208
209         write(*,*) "paleoclimate step (Earth years) "
210         paleoyears=10000. ! default value
211         call getin("paleoyears",paleoyears)
212         write(*,*) " paleoyears = ",paleoyears
213
214!***************************************************************
215         !! Radiative transfer options
216
217         write(*,*) "call radiative transfer ?"
218         callrad=.true. ! default value
219         call getin("callrad",callrad)
220         write(*,*) " callrad = ",callrad
221
222         write(*,*)"rad.transfer is computed every iradia",
223     &             " physical timestep"
224         iradia=1 ! default value
225         call getin("iradia",iradia)
226         write(*,*)" iradia = ",iradia
227
228         write(*,*) "call correlated-k radiative transfer ?"
229         corrk=.true. ! default value
230         call getin("corrk",corrk)
231         write(*,*) " corrk = ",corrk
232
233         write(*,*) "call specific cooling for radiative transfer ?"
234         cooling=.false. ! default value
235         call getin("cooling",cooling)
236         write(*,*) " cooling = ",cooling
237
238         write(*,*) "fixed gaseous CH4 mixing ratio for rad transfer ?"
239         ch4fix=.false. ! default value
240         call getin("ch4fix",ch4fix)
241         write(*,*) " ch4fix = ",ch4fix
242         write(*,*) "fixed gaseous CH4 mixing ratio for rad transfer ?"
243         vmrch4fix=0.5 ! default value
244         call getin("vmrch4fix",vmrch4fix)
245         write(*,*) " vmrch4fix = ",vmrch4fix
246         vmrch4_proffix=.false. ! default value
247         call getin("vmrch4_proffix",vmrch4_proffix)
248         write(*,*) " vmrch4_proffix = ",vmrch4_proffix
249
250         write(*,*) "NLTE correction for methane heating rates?"
251         nlte=.false.  ! default value
252         call getin("nlte",nlte)
253         write(*,*) " nlte = ",nlte
254         strobel=.false.  ! default value
255         call getin("strobel",strobel)
256         write(*,*) " strobel = ",strobel
257
258         write(*,*) "call gaseous absorption in the visible bands?"
259         callgasvis=.false. ! default value
260         call getin("callgasvis",callgasvis)
261         write(*,*) " callgasvis = ",callgasvis
262
263         write(*,*)"Output mean OLR in 1D?"
264         meanOLR=.false.
265         call getin("meanOLR",meanOLR)
266         write(*,*)" meanOLR = ",meanOLR
267
268         write(*,*)"Output spectral OLR in 3D?"
269         specOLR=.false.
270         call getin("specOLR",specOLR)
271         write(*,*)" specOLR = ",specOLR
272
273!***************************************************************
274         !! From generic model - to be cleaned
275
276         write(*,*)"Which star?"
277         startype=1 ! default value = Sol
278         call getin("startype",startype)
279         write(*,*)" startype = ",startype
280         write(*,*)"Value of stellar flux at 1 AU?"
281         Fat1AU=1366.0 ! default value = Sol today
282         call getin("Fat1AU",Fat1AU)
283         write(*,*)" Fat1AU = ",Fat1AU
284         write(*,*)"Default planetary temperature?"
285         tplanet=100.0
286         call getin("tplanet",tplanet)
287         write(*,*)" tplanet = ",tplanet
288
289!***************************************************************
290         !! TRACERS options
291
292         write(*,*) "call N2 condensation ?"
293         N2cond=.true. ! default value
294         call getin("N2cond",N2cond)
295         write(*,*) " N2cond = ",N2cond
296
297         write(*,*) "call N2 cloud condensation ?"
298         condensn2=.false. ! default value
299         call getin("condensn2",condensn2)
300         write(*,*) "condensn2 = ",condensn2
301
302         write(*,*) "call no N2 frost formation?"
303         no_n2frost=.false. ! default value
304         call getin("no_n2frost",no_n2frost)
305         write(*,*) "no_n2frost = ",no_n2frost
306
307         write(*,*) "N2 condensation subtimestep?"
308         nbsub=20 ! default value
309         call getin("nbsub",nbsub)
310         write(*,*) " nbsub = ",nbsub
311
312         write(*,*) "Gravitationnal sedimentation ?"
313         sedimentation=.true. ! default value
314         call getin("sedimentation",sedimentation)
315         write(*,*) " sedimentation = ",sedimentation
316
317         write(*,*) "Compute glacial flow ?"
318         glaflow=.false. ! default value
319         call getin("glaflow",glaflow)
320         write(*,*) " glaflow = ",glaflow
321
322         write(*,*) "Compute methane cycle ?"
323         methane=.false. ! default value
324         call getin("methane",methane)
325         write(*,*) " methane = ",methane
326         condmetsurf=.true. ! default value
327         call getin("condmetsurf",condmetsurf)
328         write(*,*) " condmetsurf = ",condmetsurf
329
330         write(*,*) "Compute methane clouds ?"
331         metcloud=.false. ! default value
332         call getin("metcloud",metcloud)
333         write(*,*) " metcloud = ",metcloud
334
335         write(*,*) "Compute CO cycle ?"
336         carbox=.false. ! default value
337         call getin("carbox",carbox)
338         write(*,*) " carbox = ",carbox
339         condcosurf=.true. ! default value
340         call getin("condcosurf",condcosurf)
341         write(*,*) " condcosurf = ",condcosurf
342
343         write(*,*) "Compute CO clouds ?"
344         monoxcloud=.false. ! default value
345         call getin("monoxcloud",monoxcloud)
346         write(*,*) " monoxcloud = ",monoxcloud
347
348         write(*,*)"atmospheric redistribution (s):"
349         tau_n2=1. ! default value
350         call getin("tau_n2",tau_n2)
351         write(*,*)" tau_n2 = ",tau_n2
352         tau_ch4=1.E7 ! default value
353         call getin("tau_ch4",tau_ch4)
354         write(*,*)" tau_ch4 = ",tau_ch4
355         tau_co=1. ! default value
356         call getin("tau_co",tau_co)
357         write(*,*)" tau_co = ",tau_co
358         tau_prechaze=1. ! default value
359         call getin("tau_prechaze",tau_prechaze)
360         write(*,*)" tau_prechaze = ",tau_prechaze
361
362         write(*,*) "Day fraction for limited cold trap in SP?"
363         dayfrac=0. ! default value
364         call getin("dayfrac",dayfrac)
365         write(*,*) " dayfrac = ",dayfrac
366         thresh_non2=0. ! default value
367         call getin("thresh_non2",thresh_non2)
368         write(*,*) " thresh_non2 = ",thresh_non2
369
370!***************************************************************
371         !! Haze options
372
373         write(*,*)"Production of haze ?"
374         haze=.false. ! default value
375         call getin("haze",haze)
376         write(*,*)" haze = ",haze
377         hazeconservch4=.false. ! conservch4, by default value ch4 is photolyzed
378         call getin("hazeconservch4",hazeconservch4)
379         write(*,*)"hazconservch4 = ",hazeconservch4
380         write(*,*)"Production of haze (fast version) ?"
381         fasthaze=.false. ! default value
382         call getin("fasthaze",fasthaze)
383         write(*,*)"fasthaze = ",fasthaze
384
385         write(*,*)"Add source of haze ?"
386         source_haze=.false. ! default value
387         call getin("source_haze",source_haze)
388         write(*,*)" source_haze = ",source_haze
389         mode_hs=0 ! mode haze source default value
390         call getin("mode_hs",mode_hs)
391         write(*,*)" mode_hs",mode_hs
392         kfix=1 ! default value
393         call getin("kfix",kfix)
394         write(*,*)"levels kfix",kfix
395         fracsource=0.1 ! default value
396         call getin("fracsource",fracsource)
397         write(*,*)" fracsource",fracsource
398         latsource=30. ! default value
399         call getin("latsource",latsource)
400         write(*,*)" latsource",latsource
401         lonsource=180. ! default value
402         call getin("lonsource",lonsource)
403         write(*,*)" lonsource",lonsource
404
405         write(*,*)"Radiatively active haze ?"
406         aerohaze=.false. ! default value
407         call getin("aerohaze",aerohaze)
408         write(*,*)"aerohaze = ",aerohaze
409
410         write(*,*)"Haze monomer radius ?"
411         rad_haze=10.e-9 ! default value
412         call getin("rad_haze",rad_haze)
413         write(*,*)"rad_haze = ",rad_haze
414
415         write(*,*)"fractal particle ?"
416         fractal=.false. ! default value
417         call getin("fractal",fractal)
418         write(*,*)"fractal = ",fractal
419         nb_monomer=10 ! default value
420         call getin("nb_monomer",nb_monomer)
421         write(*,*)"nb_monomer = ",nb_monomer
422         
423         write(*,*)"fixed radius profile from txt file ?"
424         haze_radproffix=.false. ! default value
425         call getin("haze_radproffix",haze_radproffix)
426         write(*,*)"haze_radproffix = ",haze_radproffix
427         write(*,*)"fixed MMR profile from txt file ?"
428         haze_proffix=.false. ! default value
429         call getin("haze_proffix",haze_proffix)
430         write(*,*)"haze_proffix = ",haze_proffix
431
432         write(*,*)"Number mix ratio of haze particles for co clouds:"
433         Nmix_co=100000. ! default value
434         call getin("Nmix_co",Nmix_co)
435         write(*,*)" Nmix_co = ",Nmix_co
436
437         write(*,*)"Number mix ratio of haze particles for ch4 clouds:"
438         Nmix_ch4=100000. ! default value
439         call getin("Nmix_ch4",Nmix_ch4)
440         write(*,*)" Nmix_ch4 = ",Nmix_ch4
441
442!***************************************************************
443         !! Surface properties
444
445!*********** N2 *********************************
446
447         write(*,*) "Mode for changing N2 albedo"
448         mode_n2=0 ! default value
449         call getin("mode_n2",mode_n2)
450         write(*,*) " mode_n2 = ",mode_n2
451         thres_n2ice=1. ! default value
452         call getin("thres_n2ice",thres_n2ice)
453         write(*,*) " thres_n2ice = ",thres_n2ice
454
455         write(*,*) "Diff of N2 albedo with thickness"
456         deltab=0. ! default value
457         call getin("deltab",deltab)
458         write(*,*) " deltab = ",deltab
459
460         write(*,*) "albedo N2 beta "
461         alb_n2b=0.7 ! default value
462         call getin("alb_n2b",alb_n2b)
463         write(*,*) " alb_n2b = ",alb_n2b
464
465         write(*,*) "albedo N2 alpha "
466         alb_n2a=0.7 ! default value
467         call getin("alb_n2a",alb_n2a)
468         write(*,*) " alb_n2a = ",alb_n2a
469
470         write(*,*) "emis N2 beta "
471         emis_n2b=0.7 ! default value
472         call getin("emis_n2b",emis_n2b)
473         write(*,*) " emis_n2b = ",emis_n2b
474
475         write(*,*) "emis N2 alpha "
476         emis_n2a=0.7 ! default value
477         call getin("emis_n2a",emis_n2a)
478         write(*,*) " emis_n2a = ",emis_n2a
479
480!*********** CH4 *********************************
481
482         write(*,*) "Mode for changing CH4 albedo"
483         mode_ch4=0 ! default value
484         call getin("mode_ch4",mode_ch4)
485         write(*,*) " mode_ch4 = ",mode_ch4
486         feedback_met=0 ! default value
487         call getin("feedback_met",feedback_met)
488         write(*,*) " feedback_met = ",feedback_met
489         thres_ch4ice=1. ! default value, mm
490         call getin("thres_ch4ice",thres_ch4ice)
491         write(*,*) " thres_ch4ice = ",thres_ch4ice
492         fdch4_latn=-1.
493         fdch4_lats=0.
494         fdch4_lone=0.
495         fdch4_lonw=-1.
496         fdch4_depalb=0.5
497         fdch4_finalb=0.95
498         fdch4_maxalb=0.99
499         fdch4_ampl=200.
500         fdch4_maxice=100.
501         call getin("  fdch4_latn",fdch4_latn)
502         call getin("  fdch4_lats",fdch4_lats)
503         call getin("  fdch4_lone",fdch4_lone)
504         call getin("  fdch4_lonw",fdch4_lonw)
505         call getin("  fdch4_depalb",fdch4_depalb)
506         call getin("  fdch4_finalb",fdch4_finalb)
507         call getin("  fdch4_maxalb",fdch4_maxalb)
508         call getin("  fdch4_maxice",fdch4_maxice)
509         call getin("  fdch4_ampl",fdch4_ampl)
510         write(*,*) " Values for albedo feedback = ",fdch4_latn,
511     &    fdch4_lats,fdch4_lone,fdch4_lonw,fdch4_depalb,
512     &    fdch4_finalb,fdch4_maxalb,fdch4_maxice,fdch4_ampl
513
514         write(*,*) "Latitude for diff albedo methane"
515         metlateq=25. ! default value
516         call getin("metlateq",metlateq)
517         write(*,*) " metlateq = ",metlateq
518
519         write(*,*) "Ls1 and Ls2 for change of ch4 albedo"
520         metls1=-1. ! default value
521         metls2=-2. ! default value
522         call getin("metls1",metls1)
523         call getin("metls2",metls2)
524
525         write(*,*) "albedo CH4 "
526         alb_ch4=0.5 ! default value
527         call getin("alb_ch4",alb_ch4)
528         write(*,*) " alb_ch4 = ",alb_ch4
529
530         write(*,*) "albedo equatorial CH4 "
531         alb_ch4_eq=alb_ch4 ! default value
532         call getin("alb_ch4_eq",alb_ch4_eq)
533         write(*,*) " alb_ch4_eq = ",alb_ch4_eq
534
535         write(*,*) "albedo south hemis CH4 "
536         alb_ch4_s=alb_ch4 ! default value
537         call getin("alb_ch4_s",alb_ch4_s)
538         write(*,*) " alb_ch4_s = ",alb_ch4_s
539
540         write(*,*) "emis CH4 "
541         emis_ch4=0.5 ! default value
542         call getin("emis_ch4",emis_ch4)
543         write(*,*) " emis_ch4 = ",emis_ch4
544
545         write(*,*) "CH4 lag for n2 sublimation limitation"
546         ch4lag=.false. ! default value
547         latlag=-90. ! default value
548         vmrlag=1. ! default value
549         call getin("ch4lag",ch4lag)
550         call getin("latlag",latlag)
551         call getin("vmrlag",vmrlag)
552         write(*,*) " ch4lag = ",ch4lag
553         write(*,*) " latlag = ",latlag
554         write(*,*) " vmrlag = ",vmrlag
555
556         write(*,*) "Max temperature for surface ?"
557         tsurfmax=.false. ! default value
558         albmin_ch4=0.3 ! default value
559         call getin("tsurfmax",tsurfmax)
560         call getin("albmin_ch4",albmin_ch4)
561         write(*,*) " tsurfmax = ",tsurfmax
562         write(*,*) " albmin_ch4 = ",albmin_ch4
563
564!*********** CO *********************************
565
566         write(*,*) "albedo CO "
567         alb_co=0.4 ! default value
568         call getin("alb_co",alb_co)
569         write(*,*) " alb_co = ",alb_co
570         thres_coice=1. ! default value, mm
571         call getin("thres_coice",thres_coice)
572         write(*,*) " thres_coice = ",thres_coice
573
574         write(*,*) "emis CO "
575         emis_co=0.4 ! default value
576         call getin("emis_co",emis_co)
577         write(*,*) " emis_co = ",emis_co
578
579!*********** THOLINS *********************************
580         write(*,*) "Mode for changing tholins albedo/emis"
581         mode_tholins=0 ! default value
582         call getin("mode_tholins",mode_tholins)
583         write(*,*) " mode_tholins = ",mode_tholins
584
585         write(*,*) "albedo tho "
586         alb_tho=0.1 ! default value
587         call getin("alb_tho",alb_tho)
588         write(*,*) " alb_tho = ",alb_tho
589
590         write(*,*) "albedo tho eq"
591         alb_tho_eq=0.1 ! default value
592         call getin("alb_tho_eq",alb_tho_eq)
593         write(*,*) " alb_tho_eq = ",alb_tho_eq
594
595         write(*,*) "emis tholins "
596         emis_tho=1. ! default value
597         call getin("emis_tho",emis_tho)
598         write(*,*) " emis_tho = ",emis_tho
599
600         write(*,*) "emis tholins eq"
601         emis_tho_eq=1. ! default value
602         call getin("emis_tho_eq",emis_tho_eq)
603         write(*,*) " emis_tho_eq = ",emis_tho_eq
604
605         write(*,*) "Latitude for diff albedo tholins"
606         tholateq=25. ! default value
607         call getin("tholateq",tholateq)
608         write(*,*) " tholateq = ",tholateq
609         tholatn=-1.
610         tholats=0.
611         tholone=0.
612         tholonw=-1.
613         alb_tho_spe=0.1 ! default value
614         emis_tho_spe=1. ! default value
615         call getin("  tholatn",tholatn)
616         call getin("  tholats",tholats)
617         call getin("  tholone",tholone)
618         call getin("  tholonw",tholonw)
619         write(*,*) " Values for special tholins albedo = ",tholatn,
620     &       tholats,tholone,tholonw,alb_tho_spe,emis_tho_spe
621
622         write(*,*) "Specific albedo"
623         spelon1=-180. ! default value
624         spelon2=180. ! default value
625         spelat1=-90. ! default value
626         spelat2=90. ! default value
627         specalb=.false. ! default value
628         write(*,*) "albedo/emis spe "
629         albspe=0.1 ! default value
630         emispe=1. ! default value
631         call getin("spelon1",spelon1)
632         call getin("spelon2",spelon2)
633         call getin("spelat1",spelat1)
634         call getin("spelat2",spelat2)
635         call getin("specalb",specalb)
636         call getin("albspe",albspe)
637         call getin("emispe",emispe)
638
639         write(*,*) " specific = ",specalb
640
641!********************** TI *****************************
642
643         write(*,*) "Change TI with time"
644         changeti=.false. ! default value
645         call getin("changeti",changeti)
646         write(*,*) " changeti = ",changeti
647         changetid=.false. ! default value for diurnal TI
648         call getin("changetid",changetid)
649         write(*,*) " changetid = ",changetid
650
651         write(*,*) "IT N2 "
652         ITN2=800. ! default value
653         call getin("ITN2",ITN2)
654         write(*,*) " ITN2 = ",ITN2
655         ITN2d=20. ! default value
656         call getin("ITN2d",ITN2d)
657         write(*,*) " ITN2d = ",ITN2d
658
659         write(*,*) "IT CH4"
660         ITCH4=800. ! default value
661         call getin("ITCH4",ITCH4)
662         write(*,*) " ITCH4 = ",ITCH4
663         ITCH4d=20. ! default value
664         call getin("ITCH4d",ITCH4d)
665         write(*,*) " ITCH4d = ",ITCH4d
666
667         write(*,*) "IT H2O"
668         ITH2O=800. ! default value
669         call getin("ITH2O",ITH2O)
670         write(*,*) " ITH2O = ",ITH2O
671         ITH2Od=20. ! default value
672         call getin("ITH2Od",ITH2Od)
673         write(*,*) " ITH2Od = ",ITH2Od
674
675!***************************************************************
676         !! Other Physics Options
677
678         write(*,*)"Geothermal flux (W) at the bottom layer"
679         fluxgeo=0. ! default value
680         call getin("fluxgeo",fluxgeo)
681         write(*,*)" fluxgeo = ",fluxgeo
682
683         write(*,*)"Assymetry flux (W) at the bottom layer"
684         assymflux=.false. ! default value
685         call getin("assymflux",assymflux)
686         write(*,*)" assymflux = ",assymflux
687         write(*,*)"Geothermal flux (W) for assymetry"
688         fluxgeo2=fluxgeo ! default value
689         call getin("fluxgeo2",fluxgeo2)
690         write(*,*)" fluxgeo2 = ",fluxgeo2
691         write(*,*)"Warm patch of flux"
692         patchflux=0 ! default value
693         call getin("patchflux",patchflux)
694         write(*,*)" patchflux = ",patchflux
695         
696         write(*,*) "call turbulent vertical diffusion ?"
697         calldifv=.false. ! default value
698         call getin("calldifv",calldifv)
699         write(*,*) " calldifv = ",calldifv
700         vertdiff=.true. ! default value
701         call getin("vertdiff",vertdiff)
702         write(*,*) " vertdiff = ",vertdiff
703
704         write(*,*) "call convective adjustment ?"
705         calladj=.false. ! default value
706         call getin("calladj",calladj)
707         write(*,*) " calladj = ",calladj
708       
709         write(*,*)"call thermal conduction in the soil ?"
710         callsoil=.true. ! default value
711         call getin("callsoil",callsoil)
712         write(*,*) " callsoil = ",callsoil
713       
714         write(*,*) "photochemistry: include chemical species"
715         photochem=.false. ! default value
716         call getin("photochem",photochem)
717         write(*,*) " photochem = ",photochem
718
719         write(*,*) "call thermal conduction ?"
720         callconduct=.false. ! default value
721         call getin("callconduct",callconduct)
722         write(*,*) " callconduct = ",callconduct
723
724         write(*,*) "call phitop ?"
725         phitop=0. ! default value
726         call getin("phitop",phitop)
727         write(*,*) " phitop = ",phitop
728
729         write(*,*) "call molecular viscosity ?"
730         callmolvis=.false. ! default value
731         call getin("callmolvis",callmolvis)
732         write(*,*) " callmolvis = ",callmolvis
733
734         write(*,*) "call molecular diffusion ?"
735         callmoldiff=.false. ! default value
736         call getin("callmoldiff",callmoldiff)
737         write(*,*) " callmoldiff = ",callmoldiff
738
739c         write(*,*) "call thermosphere ?"
740c         callthermos=.false. ! default value
741c         call getin("callthermos",callthermos)
742c         write(*,*) " callthermos = ",callthermos
743
744
745c        write(*,*) "call EUV heating ?",
746c    &   " (only if callthermos=.true.)"
747c        calleuv=.false.  ! default value
748c        call getin("calleuv",calleuv)
749c        write(*,*) " calleuv = ",calleuv
750         
751c         write(*,*) "call thermospheric photochemistry ?",
752c     &   " (only if callthermos=.true.)"
753c         thermochem=.false. ! default value
754c         call getin("thermochem",thermochem)
755c         write(*,*) " thermochem = ",thermochem
756
757c        if (.not.callthermos) then
758c           if (callconduct) then
759c             print*,'if callconduct is set, callthermos must be true'
760c             stop
761c           endif       
762c          if (calleuv) then
763c            print*,'if calleuv is set, callthermos must be true'
764c            stop
765c          endif         
766
767!*************************************************************
768!*************************************************************
769!                   Tests of incompatibility:
770!*************************************************************
771!*************************************************************
772
773         if ((.not.tracer).and.(haze)) then
774           print*,'if haze are on, tracers must be on!'
775           stop
776         endif
777         if (callmolvis.and..not.callconduct) then
778             print*,'if callmolvis is set, callconduc must be true'
779             stop
780         endif       
781         if (paleo.and..not.fast) then
782             print*,'if paleo is set, fast must be true'
783             stop
784         endif       
785         if (fasthaze.and..not.fast) then
786             print*,'if fasthaze is set, fast must be true'
787             stop
788         endif       
789         if (fasthaze.and..not.methane) then
790             print*,'if fasthaze is set, methane must be true'
791             stop
792         endif       
793         if ((haze.or.fasthaze).and..not.methane) then
794             print*,'if haze/fasthaze is set, methane must be true'
795             stop
796         endif       
797         if ((haze_proffix.or.haze_radproffix).and..not.aerohaze) then
798             print*,'for now, haze/rad proffix only works w aerohaze=T'
799             stop
800         endif       
801c          if (callmoldiff) then
802c            print*,'if callmoldiff is set, callthermos must be true'
803c            stop
804c          endif         
805c          if (thermochem) then
806c            print*,'if thermochem is set, callthermos must be true'
807c            stop
808c          endif         
809c       endif
810
811         PRINT*,'--------------------------------------------'
812         PRINT*
813         PRINT*
814      ELSE
815         write(*,*)
816         write(*,*) 'Cannot read file callphys.def. Is it here ?'
817         stop
818      ENDIF
819
8208000  FORMAT(t5,a12,l8)
8218001  FORMAT(t5,a12,i8)
822
823      PRINT*
824      PRINT*,'inifis: daysec',daysec
825      PRINT*
826      PRINT*,'inifis: The radiative transfer is computed:'
827      PRINT*,'           each ',iradia,' physical time-step'
828      !PRINT*,'        or each ',iradia*dtphys,' seconds'
829      PRINT*
830
831! --------------------------------------------------------------
832!  Managing the Longwave radiative transfer
833! --------------------------------------------------------------
834
835!     In most cases, the run just use the following values :
836!     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
837      callemis=.true.     
838!     ilwd=10*int(daysec/dtphys) ! bug before 22/10/01       
839      ilwd=10*int(daysec/dtphys)
840      ilwn=2               
841      linear=.true.       
842      ncouche=3
843      alphan=0.4
844      ilwb=2
845      semi=0
846
847c$$$!     BUT people working hard on the LW may want to read them in 'radia.def'
848c$$$!     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
849c$$$
850c$$$      OPEN(99,file='radia.def',status='old',form='formatted'
851c$$$     .     ,iostat=ierr)
852c$$$      IF(ierr.EQ.0) THEN
853c$$$         write(*,*) 'inifis: Reading radia.def !!!'
854c$$$         READ(99,fmt='(a)') ch1
855c$$$         READ(99,*) callemis
856c$$$         WRITE(*,8000) ch1,callemis
857c$$$
858c$$$         READ(99,fmt='(a)') ch1
859c$$$         READ(99,*) iradia
860c$$$         WRITE(*,8001) ch1,iradia
861c$$$
862c$$$         READ(99,fmt='(a)') ch1
863c$$$         READ(99,*) ilwd
864c$$$         WRITE(*,8001) ch1,ilwd
865c$$$
866c$$$         READ(99,fmt='(a)') ch1
867c$$$         READ(99,*) ilwn
868c$$$         WRITE(*,8001) ch1,ilwn
869c$$$
870c$$$         READ(99,fmt='(a)') ch1
871c$$$         READ(99,*) linear
872c$$$         WRITE(*,8000) ch1,linear
873c$$$
874c$$$         READ(99,fmt='(a)') ch1
875c$$$         READ(99,*) ncouche
876c$$$         WRITE(*,8001) ch1,ncouche
877c$$$
878c$$$         READ(99,fmt='(a)') ch1
879c$$$         READ(99,*) alphan
880c$$$         WRITE(*,*) ch1,alphan
881c$$$
882c$$$         READ(99,fmt='(a)') ch1
883c$$$         READ(99,*) ilwb
884c$$$         WRITE(*,8001) ch1,ilwb
885c$$$
886c$$$
887c$$$         READ(99,fmt='(a)') ch1
888c$$$         READ(99,'(l1)') callg2d
889c$$$         WRITE(*,8000) ch1,callg2d
890c$$$
891c$$$         READ(99,fmt='(a)') ch1
892c$$$         READ(99,*) semi
893c$$$         WRITE(*,*) ch1,semi
894c$$$      end if
895c$$$      CLOSE(99)
896
897!-----------------------------------------------------------------------
898!     Some more initialization:
899!     ------------------------
900
901      CALL SCOPY(ngrid,plon,1,long,1)
902      CALL SCOPY(ngrid,plat,1,lati,1)
903      CALL SCOPY(ngrid,parea,1,area,1)
904      totarea=SSUM(ngridmx,area,1)
905      !! Computing realarea
906      DO ig=2,ngridmx-1
907         realarea(ig)=area(ig)
908      ENDDO
909      realarea(1)=area(1)*iim
910      realarea(ngridmx)=area(ngridmx)*iim
911
912      DO ig=1,ngrid
913         sinlat(ig)=sin(plat(ig))
914         coslat(ig)=cos(plat(ig))
915         sinlon(ig)=sin(plon(ig))
916         coslon(ig)=cos(plon(ig))
917      ENDDO
918
919      pi=2.*asin(1.) ! NB: pi is a common in comcstfi.h
920
921!     managing the tracers, and tests:
922!     -------------------------------
923
924      if(tracer) then
925
926!          when photochem is used, nqchem_min is the rank
927!          of the first chemical species
928
929! Ehouarn: nqchem_min is now meaningless and no longer used
930!       nqchem_min = 1
931       if (photochem .or. callthermos) then
932         chem = .true.
933       end if
934
935      endif ! of if (tracer)
936
937      RETURN
938      END
Note: See TracBrowser for help on using the repository browser.