source: trunk/LMDZ.MARS/libf/phymars/inifis.F @ 552

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

Mars GCM:

bug fix in "aeronomars/moldiff_red.F90" (wrong mmol array size in included

subroutine) + adapted extreme limit test for H to altitudes of ~4000km
(compatble with 50 layer model).

bug fix in "nirco2abs.F" index of "co2" and "o" tracers were hard coded as

1 and 3!

updates from FGG of euvheat.F, callkeys.h and inifis.F to have the

"euveff" parameter read from callphys.def

EM

File size: 26.8 KB
Line 
1      SUBROUTINE inifis(
2     $           ngrid,nlayer
3     $           ,day_ini,pdaysec,ptimestep
4     $           ,plat,plon,parea
5     $           ,prad,pg,pr,pcpp
6#ifdef MESOSCALE
7#include "meso_inc/meso_inc_inifisinvar.F"
8#endif
9     $           )
10!
11!=======================================================================
12!
13!   purpose:
14!   -------
15!
16!   Initialisation for the physical parametrisations of the LMD
17!   martian atmospheric general circulation modele.
18!
19!   author: Frederic Hourdin 15 / 10 /93
20!   -------
21!   modified: Sebastien Lebonnois 11/06/2003 (new callphys.def)
22!             Ehouarn Millour (oct. 2008) tracers are now identified
23!              by their names and may not be contiguously
24!              stored in the q(:,:,:,:) array
25!             E.M. (june 2009) use getin routine to load parameters
26!             adapted to the mesoscale use - Aymeric Spiga - 01/2007-07/2011
27!
28!
29!   arguments:
30!   ----------
31!
32!   input:
33!   ------
34!
35!    ngrid                 Size of the horizontal grid.
36!                          All internal loops are performed on that grid.
37!    nlayer                Number of vertical layers.
38!    pdayref               Day of reference for the simulation
39!    pday                  Number of days counted from the North. Spring
40!                          equinoxe.
41!
42!=======================================================================
43!
44!-----------------------------------------------------------------------
45!   declarations:
46!   -------------
47! to use  'getin'
48      USE ioipsl_getincom
49      IMPLICIT NONE
50#include "dimensions.h"
51#include "dimphys.h"
52#include "planete.h"
53#include "comcstfi.h"
54#include "comsaison.h"
55#include "comdiurn.h"
56#include "comgeomfi.h"
57#include "callkeys.h"
58#include "surfdat.h"
59#include "dimradmars.h"
60#include "yomaer.h"
61#include "datafile.h"
62#include "slope.h"
63#include "microphys.h"
64#include "tracer.h"
65#ifdef MESOSCALE
66#include "comsoil.h"     !!MESOSCALE -- needed to fill volcapa
67#include "meso_inc/meso_inc_inifisvar.F"
68#endif
69      REAL prad,pg,pr,pcpp,pdaysec
70
71      REAL ptimestep
72      INTEGER day_ini
73
74      INTEGER ngrid,nlayer
75      REAL plat(ngrid),plon(ngrid),parea(ngridmx)
76      INTEGER ig,ierr
77 
78!      EXTERNAL iniorbit,orbite
79      EXTERNAL SSUM
80      REAL SSUM
81 
82      CHARACTER ch1*12
83      CHARACTER ch80*80
84
85!      logical chem, h2o
86
87!      chem = .false.
88!      h2o = .false.
89
90      rad=prad
91      cpp=pcpp
92      g=pg
93      r=pr
94      rcp=r/cpp
95      daysec=pdaysec
96      dtphys=ptimestep
97#ifdef MESOSCALE
98#include "meso_inc/meso_inc_inifisini.F"
99#endif
100
101! --------------------------------------------------------
102!     The usual Tests
103!     --------------
104      IF (nlayer.NE.nlayermx) THEN
105         PRINT*,'STOP in inifis'
106         PRINT*,'Probleme de dimensions :'
107         PRINT*,'nlayer     = ',nlayer
108         PRINT*,'nlayermx   = ',nlayermx
109         STOP
110      ENDIF
111
112      IF (ngrid.NE.ngridmx) THEN
113         PRINT*,'STOP in inifis'
114         PRINT*,'Probleme de dimensions :'
115         PRINT*,'ngrid     = ',ngrid
116         PRINT*,'ngridmx   = ',ngridmx
117         STOP
118      ENDIF
119
120! --------------------------------------------------------------
121!  Reading the "callphys.def" file controlling some key options
122! --------------------------------------------------------------
123     
124      ! check that 'callphys.def' file is around
125      OPEN(99,file='callphys.def',status='old',form='formatted'
126     &     ,iostat=ierr)
127      CLOSE(99)
128     
129      IF(ierr.EQ.0) THEN
130         PRINT*
131         PRINT*
132         PRINT*,'--------------------------------------------'
133         PRINT*,' inifis: Parameters for the physics (callphys.def)'
134         PRINT*,'--------------------------------------------'
135
136         write(*,*) "Directory where external input files are:"
137         datafile="/u/forget/WWW/datagcm/datafile"
138         call getin("datadir",datafile) ! default path
139         write(*,*) " datafile = ",trim(datafile)
140
141         write(*,*) "Run with or without tracer transport ?"
142         tracer=.false. ! default value
143         call getin("tracer",tracer)
144         write(*,*) " tracer = ",tracer
145
146         write(*,*) "Diurnal cycle ?"
147         write(*,*) "(if diurnal=False, diurnal averaged solar heating)"
148         diurnal=.true. ! default value
149         call getin("diurnal",diurnal)
150         write(*,*) " diurnal = ",diurnal
151
152         write(*,*) "Seasonal cycle ?"
153         write(*,*) "(if season=False, Ls stays constant, to value ",
154     &   "set in 'start'"
155         season=.true. ! default value
156         call getin("season",season)
157         write(*,*) " season = ",season
158
159         write(*,*) "Write some extra output to the screen ?"
160         lwrite=.false. ! default value
161         call getin("lwrite",lwrite)
162         write(*,*) " lwrite = ",lwrite
163
164         write(*,*) "Save statistics in file stats.nc ?"
165#ifdef MESOSCALE
166         callstats=.false. ! default value
167#else
168         callstats=.true. ! default value
169#endif
170         call getin("callstats",callstats)
171         write(*,*) " callstats = ",callstats
172
173         write(*,*) "Save EOF profiles in file 'profiles' for ",
174     &              "Climate Database?"
175         calleofdump=.false. ! default value
176         call getin("calleofdump",calleofdump)
177         write(*,*) " calleofdump = ",calleofdump
178
179         write(*,*) "Dust scenario: 1=constant dust (read from startfi",
180     &   " or set as tauvis); 2=Viking scenario; =3 MGS scenario,",
181     &   "=4 Mars Year 24 from TES assimilation, ",
182     &   "=24,25 or 26 :Mars Year 24,25 or 26 from TES assimilation"
183         iaervar=3 ! default value
184         call getin("iaervar",iaervar)
185         write(*,*) " iaervar = ",iaervar
186
187         write(*,*) "Reference (visible) dust opacity at 700 Pa ",
188     &   "(matters only if iaervar=1)"
189         ! NB: default value of tauvis is set/read in startfi.nc file
190         call getin("tauvis",tauvis)
191         write(*,*) " tauvis = ",tauvis
192
193         write(*,*) "Dust vertical distribution:"
194         write(*,*) "(=1 top set by topdustref parameter;",
195     & " =2 Viking scenario; =3 MGS scenario)"
196         iddist=3 ! default value
197         call getin("iddist",iddist)
198         write(*,*) " iddist = ",iddist
199
200         write(*,*) "Dust top altitude (km). (Matters only if iddist=1)"
201         topdustref= 90.0 ! default value
202         call getin("topdustref",topdustref)
203         write(*,*) " topdustref = ",topdustref
204
205         write(*,*) "Prescribed surface thermal flux (H/(rho*cp),K m/s)"
206         tke_heat_flux=0. ! default value
207         call getin("tke_heat_flux",tke_heat_flux)
208         write(*,*) " tke_heat_flux = ",tke_heat_flux
209         write(*,*) " 0 means the usual schemes are computing"
210
211         write(*,*) "call radiative transfer ?"
212         callrad=.true. ! default value
213         call getin("callrad",callrad)
214         write(*,*) " callrad = ",callrad
215
216         write(*,*) "call slope insolation scheme ?",
217     &              "(matters only if callrad=T)"
218#ifdef MESOSCALE
219         callslope=.true. ! default value
220#else
221         callslope=.false. ! default value (not supported yet)
222#endif
223         call getin("callslope",callslope)
224         write(*,*) " callslope = ",callslope
225
226         write(*,*) "call NLTE radiative schemes ?",
227     &              "(matters only if callrad=T)"
228         callnlte=.false. ! default value
229         call getin("callnlte",callnlte)
230         write(*,*) " callnlte = ",callnlte
231         
232         nltemodel=0    !default value
233         write(*,*) "NLTE model?"
234         write(*,*) "0 -> old model, static O"
235         write(*,*) "1 -> old model, dynamic O"
236         write(*,*) "2 -> new model"
237         write(*,*) "(matters only if callnlte=T)"
238         call getin("nltemodel",nltemodel)
239         write(*,*) " nltemodel = ",nltemodel
240
241         write(*,*) "call CO2 NIR absorption ?",
242     &              "(matters only if callrad=T)"
243         callnirco2=.false. ! default value
244         call getin("callnirco2",callnirco2)
245         write(*,*) " callnirco2 = ",callnirco2
246
247         write(*,*) "New NIR NLTE correction ?",
248     $              "0-> old model (no correction)",
249     $              "1-> new correction",
250     $              "(matters only if callnirco2=T)"
251         nircorr=1      !default value
252         call getin("nircorr",nircorr)
253         write(*,*) " nircorr = ",nircorr
254
255         write(*,*) "call turbulent vertical diffusion ?"
256         calldifv=.true. ! default value
257         call getin("calldifv",calldifv)
258         write(*,*) " calldifv = ",calldifv
259
260         write(*,*) "call thermals ?"
261         calltherm=.false. ! default value
262         call getin("calltherm",calltherm)
263         write(*,*) " calltherm = ",calltherm
264
265         write(*,*) "output thermal diagnostics ?"
266         outptherm=.false. ! default value
267         call getin("outptherm",outptherm)
268         write(*,*) " outptherm = ",outptherm
269
270         write(*,*) "call convective adjustment ?"
271         calladj=.true. ! default value
272         call getin("calladj",calladj)
273         write(*,*) " calladj = ",calladj
274         
275         if (calltherm .and. (.not. calladj)) then
276          print*,'Convadj has to be activated when using thermals'
277          stop
278         endif
279
280         write(*,*) "call Richardson-based surface layer ?"
281         callrichsl=.false. ! default value
282         call getin("callrichsl",callrichsl)
283         write(*,*) " callrichsl = ",callrichsl
284
285         if (calltherm .and. .not.callrichsl) then
286          print*,'WARNING WARNING WARNING'
287          print*,'if calltherm=T we strongly advise that '
288          print*,'you use the new surface layer scheme '
289          print*,'by setting callrichsl=T '
290         endif
291
292         if (calladj .and. callrichsl) then
293          print*,'You should not be calling the convective adjustment
294     & scheme with the Richardson surface-layer. This approach is not
295     & physically consistent and can lead to unrealistic friction
296     & values.'
297          print*,'If you want to use the Ri. surface-layer, either
298     & activate thermals OR de-activate the convective adjustment.'
299          stop
300         endif
301
302         write(*,*) "call CO2 condensation ?"
303         callcond=.true. ! default value
304         call getin("callcond",callcond)
305         write(*,*) " callcond = ",callcond
306
307         write(*,*)"call thermal conduction in the soil ?"
308         callsoil=.true. ! default value
309         call getin("callsoil",callsoil)
310         write(*,*) " callsoil = ",callsoil
311         
312
313         write(*,*)"call Lott's gravity wave/subgrid topography ",
314     &             "scheme ?"
315         calllott=.true. ! default value
316         call getin("calllott",calllott)
317         write(*,*)" calllott = ",calllott
318
319
320         write(*,*)"rad.transfer is computed every iradia",
321     &             " physical timestep"
322         iradia=1 ! default value
323         call getin("iradia",iradia)
324         write(*,*)" iradia = ",iradia
325         
326
327         write(*,*)"Output of the exchange coefficient mattrix ?",
328     &             "(for diagnostics only)"
329         callg2d=.false. ! default value
330         call getin("callg2d",callg2d)
331         write(*,*)" callg2d = ",callg2d
332
333         write(*,*)"Rayleigh scattering : (should be .false. for now)"
334         rayleigh=.false.
335         call getin("rayleigh",rayleigh)
336         write(*,*)" rayleigh = ",rayleigh
337
338
339! TRACERS:
340
341! dustbin
342         write(*,*)"Transported dust ? (if >0, use 'dustbin' dust bins)"
343         dustbin=0 ! default value
344         call getin("dustbin",dustbin)
345         write(*,*)" dustbin = ",dustbin
346! active
347         write(*,*)"Radiatively active dust ? (matters if dustbin>0)"
348         active=.false. ! default value
349         call getin("active",active)
350         write(*,*)" active = ",active
351
352! Test of incompatibility:
353! if active is used, then dustbin should be > 0
354
355         if (active.and.(dustbin.lt.1)) then
356           print*,'if active is used, then dustbin should > 0'
357           stop
358         endif
359! doubleq
360         write(*,*)"use mass and number mixing ratios to predict",
361     &             " dust size ?"
362         doubleq=.false. ! default value
363         call getin("doubleq",doubleq)
364         write(*,*)" doubleq = ",doubleq
365! submicron
366         submicron=.false. ! default value
367         call getin("submicron",submicron)
368         write(*,*)" submicron = ",submicron
369
370! Test of incompatibility:
371! if doubleq is used, then dustbin should be 2
372
373         if (doubleq.and.(dustbin.ne.2)) then
374           print*,'if doubleq is used, then dustbin should be 2'
375           stop
376         endif
377         if (doubleq.and.submicron.and.(nqmx.LT.3)) then
378           print*,'If doubleq is used with a submicron tracer,'
379           print*,' then the number of tracers has to be'
380           print*,' larger than 3.'
381           stop
382         endif
383! lifting
384         write(*,*)"dust lifted by GCM surface winds ?"
385         lifting=.false. ! default value
386         call getin("lifting",lifting)
387         write(*,*)" lifting = ",lifting
388
389! Test of incompatibility:
390! if lifting is used, then dustbin should be > 0
391
392         if (lifting.and.(dustbin.lt.1)) then
393           print*,'if lifting is used, then dustbin should > 0'
394           stop
395         endif
396! callddevil
397         write(*,*)" dust lifted by dust devils ?"
398         callddevil=.false. !default value
399         call getin("callddevil",callddevil)
400         write(*,*)" callddevil = ",callddevil
401
402! Test of incompatibility:
403! if dustdevil is used, then dustbin should be > 0
404
405         if (callddevil.and.(dustbin.lt.1)) then
406           print*,'if dustdevil is used, then dustbin should > 0'
407           stop
408         endif
409! sedimentation
410         write(*,*) "Gravitationnal sedimentation ?"
411         sedimentation=.true. ! default value
412         call getin("sedimentation",sedimentation)
413         write(*,*) " sedimentation = ",sedimentation
414! activice
415         write(*,*) "Radiatively active transported atmospheric ",
416     &              "water ice ?"
417         activice=.false. ! default value
418         call getin("activice",activice)
419         write(*,*) " activice = ",activice
420! water
421         write(*,*) "Compute water cycle ?"
422         water=.false. ! default value
423         call getin("water",water)
424         write(*,*) " water = ",water
425
426! Test of incompatibility:
427
428         if (activice.and..not.water) then
429           print*,'if activice is used, water should be used too'
430           stop
431         endif
432
433         if (water.and..not.tracer) then
434           print*,'if water is used, tracer should be used too'
435           stop
436         endif
437         
438! water ice clouds effective variance distribution for sedimentaion       
439        write(*,*) "effective variance for water ice clouds ?"
440        nuice_sed=0.45
441        call getin("nuice_sed",nuice_sed)
442        write(*,*) "water_param nueff Sedimentation:", nuice_sed
443         
444! ccn factor if no scavenging         
445        write(*,*) "water param CCN reduc. factor ?", ccn_factor
446        ccn_factor = 4.5
447        call getin("ccn_factor",ccn_factor)
448        write(*,*)" ccn_factor = ",ccn_factor
449        write(*,*)"Careful: only used when microphys=F, otherwise"
450        write(*,*)"the contact parameter is used instead;"
451
452! microphys
453         write(*,*)"Microphysical scheme for water-ice clouds?"
454         microphys=.false. ! default value
455         call getin("microphys",microphys)
456         write(*,*)" microphys = ",microphys
457
458! microphysical parameter contact       
459         write(*,*) "water contact parameter ?"
460         mteta  = 0.95
461         call getin("mteta",mteta)
462         write(*,*) "mteta = ", mteta
463
464! scavenging
465         write(*,*)"Dust scavenging by H2O/CO2 snowfall ?"
466         scavenging=.false. ! default value
467         call getin("scavenging",scavenging)
468         write(*,*)" scavenging = ",scavenging
469         
470
471! Test of incompatibility:
472! if scavenging is used, then dustbin should be > 0
473
474         if (scavenging.and.(dustbin.lt.1)) then
475           print*,'if scavenging is used, then dustbin should > 0'
476           stop
477         endif
478         if ((microphys.and..not.doubleq).or.
479     &       (microphys.and..not.active).or.
480     &       (microphys.and..not.scavenging).or.
481     &       (microphys.and..not.water)) then
482           print*,'if microphys is used, then doubleq,'
483           print*,'active, water and scavenging must all be used!'
484           stop
485         endif
486         if ((scavenging.and..not.doubleq).or.
487     &       (scavenging.and..not.active).or.
488     &       (scavenging.and..not.water).or.
489     &       (scavenging.and..not.microphys)) then
490           print*,'if scavenging is used, then doubleq,'
491           print*,'active, water and microphys must all be used!'
492           stop
493         endif
494
495! Test of incompatibility:
496
497         write(*,*) "Permanent water caps at poles ?",
498     &               " .true. is RECOMMENDED"
499         write(*,*) "(with .true., North cap is a source of water ",
500     &   "and South pole is a cold trap)"
501         caps=.true. ! default value
502         call getin("caps",caps)
503         write(*,*) " caps = ",caps
504
505! albedo_h2o_ice
506         write(*,*) "water ice albedo ?"
507         albedo_h2o_ice=0.45
508         call getin("albedo_h2o_ice",albedo_h2o_ice)
509         write(*,*) " albedo_h2o_ice = ",albedo_h2o_ice
510! inert_h2o_ice
511         write(*,*) "water ice thermal inertia ?"
512         inert_h2o_ice=2400 ! (J.m^-2.K^-1.s^-1/2)
513         call getin("inert_h2o_ice",inert_h2o_ice)
514         write(*,*) " inert_h2o_ice = ",inert_h2o_ice
515! frost_albedo_threshold
516         write(*,*) "frost thickness threshold for albedo ?"
517         frost_albedo_threshold=0.005 ! 5.4 mic (i.e 0.005 kg.m-2)
518         call getin("frost_albedo_threshold",
519     &    frost_albedo_threshold)
520         write(*,*) " frost_albedo_threshold = ",
521     &            frost_albedo_threshold
522
523! call Titus crocus line -- DEFAULT IS NONE
524         write(*,*) "Titus crocus line ?"
525         tituscap=.false.  ! default value
526         call getin("tituscap",tituscap)
527         write(*,*) "tituscap",tituscap
528
529!!!!!!!!!!!!!!!! TEMP !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
530!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!     
531         write(*,*) "temp tag for water caps ?"
532         temptag=.false.
533         call getin("temptag",temptag)
534         write(*,*) " temptag = ",temptag
535!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
536!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!             
537
538         write(*,*) "photochemistry: include chemical species"
539         photochem=.false. ! default value
540         call getin("photochem",photochem)
541         write(*,*) " photochem = ",photochem
542
543
544! THERMOSPHERE
545
546         write(*,*) "call thermosphere ?"
547         callthermos=.false. ! default value
548         call getin("callthermos",callthermos)
549         write(*,*) " callthermos = ",callthermos
550         
551
552         write(*,*) " water included without cycle ",
553     &              "(only if water=.false.)"
554         thermoswater=.false. ! default value
555         call getin("thermoswater",thermoswater)
556         write(*,*) " thermoswater = ",thermoswater
557
558         write(*,*) "call thermal conduction ?",
559     &    " (only if callthermos=.true.)"
560         callconduct=.false. ! default value
561         call getin("callconduct",callconduct)
562         write(*,*) " callconduct = ",callconduct
563
564         write(*,*) "call EUV heating ?",
565     &   " (only if callthermos=.true.)"
566         calleuv=.false.  ! default value
567         call getin("calleuv",calleuv)
568         write(*,*) " calleuv = ",calleuv
569
570         write(*,*) "call molecular viscosity ?",
571     &   " (only if callthermos=.true.)"
572         callmolvis=.false. ! default value
573         call getin("callmolvis",callmolvis)
574         write(*,*) " callmolvis = ",callmolvis
575
576         write(*,*) "call molecular diffusion ?",
577     &   " (only if callthermos=.true.)"
578         callmoldiff=.false. ! default value
579         call getin("callmoldiff",callmoldiff)
580         write(*,*) " callmoldiff = ",callmoldiff
581         
582
583         write(*,*) "call thermospheric photochemistry ?",
584     &   " (only if callthermos=.true.)"
585         thermochem=.false. ! default value
586         call getin("thermochem",thermochem)
587         write(*,*) " thermochem = ",thermochem
588
589         write(*,*) "date for solar flux calculation:",
590     &   " (1985 < date < 2002)"
591         write(*,*) "(Solar min=1996.4 ave=1993.4 max=1990.6)"
592         solarcondate=1993.4 ! default value
593         call getin("solarcondate",solarcondate)
594         write(*,*) " solarcondate = ",solarcondate
595         
596         write(*,*) "UV heating efficiency:",
597     &   "measured values between 0.19 and 0.23 (Fox et al. 1996)",
598     &   "lower values may be used to compensate low 15 um cooling"
599         euveff=0.21 !default value
600         call getin("euveff",euveff)
601         write(*,*) " euveff = ", euveff
602
603         if (.not.callthermos) then
604           if (thermoswater) then
605             print*,'if thermoswater is set, callthermos must be true'
606             stop
607           endif         
608           if (callconduct) then
609             print*,'if callconduct is set, callthermos must be true'
610             stop
611           endif       
612           if (calleuv) then
613             print*,'if calleuv is set, callthermos must be true'
614             stop
615           endif         
616           if (callmolvis) then
617             print*,'if callmolvis is set, callthermos must be true'
618             stop
619           endif       
620           if (callmoldiff) then
621             print*,'if callmoldiff is set, callthermos must be true'
622             stop
623           endif         
624           if (thermochem) then
625             print*,'if thermochem is set, callthermos must be true'
626             stop
627           endif         
628        endif
629
630! Test of incompatibility:
631! if photochem is used, then water should be used too
632
633         if (photochem.and..not.water) then
634           print*,'if photochem is used, water should be used too'
635           stop
636         endif
637
638! if callthermos is used, then thermoswater should be used too
639! (if water not used already)
640
641         if (callthermos .and. .not.water) then
642           if (callthermos .and. .not.thermoswater) then
643             print*,'if callthermos is used, water or thermoswater
644     &               should be used too'
645             stop
646           endif
647         endif
648
649         PRINT*,'--------------------------------------------'
650         PRINT*
651         PRINT*
652      ELSE
653         write(*,*)
654         write(*,*) 'Cannot read file callphys.def. Is it here ?'
655         stop
656      ENDIF
657
6588000  FORMAT(t5,a12,l8)
6598001  FORMAT(t5,a12,i8)
660
661      PRINT*
662      PRINT*,'inifis: daysec',daysec
663      PRINT*
664      PRINT*,'inifis: The radiative transfer is computed:'
665      PRINT*,'           each ',iradia,' physical time-step'
666      PRINT*,'        or each ',iradia*dtphys,' seconds'
667      PRINT*
668! --------------------------------------------------------------
669!  Managing the Longwave radiative transfer
670! --------------------------------------------------------------
671
672!     In most cases, the run just use the following values :
673!     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
674      callemis=.true.     
675!     ilwd=10*int(daysec/dtphys) ! bug before 22/10/01       
676      ilwd=1
677      ilwn=1 !2
678      ilwb=1 !2
679      linear=.true.       
680      ncouche=3
681      alphan=0.4
682      semi=0
683
684!     BUT people working hard on the LW may want to read them in 'radia.def'
685!     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
686
687      OPEN(99,file='radia.def',status='old',form='formatted'
688     .     ,iostat=ierr)
689      IF(ierr.EQ.0) THEN
690         write(*,*) 'inifis: Reading radia.def !!!'
691         READ(99,fmt='(a)') ch1
692         READ(99,*) callemis
693         WRITE(*,8000) ch1,callemis
694
695         READ(99,fmt='(a)') ch1
696         READ(99,*) iradia
697         WRITE(*,8001) ch1,iradia
698
699         READ(99,fmt='(a)') ch1
700         READ(99,*) ilwd
701         WRITE(*,8001) ch1,ilwd
702
703         READ(99,fmt='(a)') ch1
704         READ(99,*) ilwn
705         WRITE(*,8001) ch1,ilwn
706
707         READ(99,fmt='(a)') ch1
708         READ(99,*) linear
709         WRITE(*,8000) ch1,linear
710
711         READ(99,fmt='(a)') ch1
712         READ(99,*) ncouche
713         WRITE(*,8001) ch1,ncouche
714
715         READ(99,fmt='(a)') ch1
716         READ(99,*) alphan
717         WRITE(*,*) ch1,alphan
718
719         READ(99,fmt='(a)') ch1
720         READ(99,*) ilwb
721         WRITE(*,8001) ch1,ilwb
722
723
724         READ(99,fmt='(a)') ch1
725         READ(99,'(l1)') callg2d
726         WRITE(*,8000) ch1,callg2d
727
728         READ(99,fmt='(a)') ch1
729         READ(99,*) semi
730         WRITE(*,*) ch1,semi
731      end if
732      CLOSE(99)
733
734!-----------------------------------------------------------------------
735!     Some more initialization:
736!     ------------------------
737
738      ! in 'comgeomfi.h'
739      CALL SCOPY(ngrid,plon,1,long,1)
740      CALL SCOPY(ngrid,plat,1,lati,1)
741      CALL SCOPY(ngrid,parea,1,area,1)
742      totarea=SSUM(ngridmx,area,1)
743
744      ! in 'comdiurn.h'
745      DO ig=1,ngrid
746         sinlat(ig)=sin(plat(ig))
747         coslat(ig)=cos(plat(ig))
748         sinlon(ig)=sin(plon(ig))
749         coslon(ig)=cos(plon(ig))
750      ENDDO
751
752      pi=2.*asin(1.) ! NB: pi is a common in comcstfi.h
753
754!     managing the tracers, and tests:
755!     -------------------------------
756!     Ehouarn: removed; as these tests are now done in initracer.F
757!      if(tracer) then
758!
759!!          when photochem is used, nqchem_min is the rank
760!!          of the first chemical species
761!
762!! Ehouarn: nqchem_min is now meaningless and no longer used
763!!       nqchem_min = 1
764!       if (photochem .or. callthermos) then
765!         chem = .true.
766!       end if
767!
768!       if (water .or. thermoswater) h2o = .true.
769!
770!!          TESTS
771!
772!       print*,'inifis: TRACERS:'
773!       write(*,*) "    chem=",chem,"    h2o=",h2o
774!!       write(*,*) "   doubleq=",doubleq
775!!       write(*,*) "   dustbin=",dustbin
776!
777!       if ((doubleq).and.(h2o).and.
778!     $     (chem)) then
779!         print*,' 2 dust tracers (doubleq)'
780!         print*,' 1 water vapour tracer'
781!         print*,' 1 water ice tracer'
782!         print*,nqmx-4,' chemistry tracers'
783!       endif
784!
785!       if ((doubleq).and.(h2o).and.
786!     $     .not.(chem)) then
787!         print*,' 2 dust tracers (doubleq)'
788!         print*,' 1 water vapour tracer'
789!         print*,' 1 water ice tracer'
790!         if (nqmx.LT.4) then
791!           print*,'nqmx should be at least equal to'
792!           print*,'4 with these options.'
793!           stop
794!         endif
795!       endif
796!
797!       if (.not.(doubleq).and.(h2o).and.
798!     $     (chem)) then
799!         if (dustbin.gt.0) then
800!           print*,dustbin,' dust bins'
801!         endif
802!         print*,nqmx-2-dustbin,' chemistry tracers'
803!         print*,' 1 water vapour tracer'
804!         print*,' 1 water ice tracer'
805!       endif
806!
807!       if (.not.(doubleq).and.(h2o).and.
808!     $     .not.(chem)) then
809!         if (dustbin.gt.0) then
810!           print*,dustbin,' dust bins'
811!         endif
812!         print*,' 1 water vapour tracer'
813!         print*,' 1 water ice tracer'
814!         if (nqmx.gt.(dustbin+2)) then
815!           print*,'nqmx should be ',(dustbin+2),
816!     $            ' with these options...'
817!                  print*,'(or check callphys.def)'
818!         endif
819!         if (nqmx.lt.(dustbin+2)) then
820!           write(*,*) "inifis: nqmx.lt.(dustbin+2)"
821!           stop
822!         endif
823!       endif
824!
825!      endif ! of if (tracer)
826!
827!      RETURN
828      END
Note: See TracBrowser for help on using the repository browser.