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

Last change on this file since 390 was 358, checked in by aslmd, 14 years ago

LMDZ.MARS:


A FIRST VERSION WITH SCAVENGING
TRANSPARENT TO CASUAL USER
FOR WATER CYCLE FOLKS, SEE BELOW


[TN and AS solved conflicts due to r330 >> r357]


07/11/11 == JBM

Changed watercloud.F to call two separate routines,

simpleclouds.F or improvedclouds.F, which are a simplified and
full microphysical scheme for cloud formation, respectively.
Removed the tag called "improved" in watercloud.F, and added
another tag called "microphys" which is defined in callphys.F
instead. Changed routines: callkeys, inifis, physiq, watercloud.

Reimplemented the use of typical profiles of dust particle sizes

and CCNs in simpleclouds.F. Corrected the previously used
analytical CCN profile. Moved ccn_factor to simpleclouds.F,
which won't be used in the new microphysical scheme. Changed
routines: aeropacity, physiq, simpleclouds, watercloud.

Computed rdust at the end of callsedim instead of updatereffrad,

except at firstcall. Renamed rfall into rsedcloud and moved it
in simpleclouds. Moved nuice_sed to initracer.F and added it to
tracer.h. Changed routines: callsedim, physiq, tracer.h,
watercloud, initracer, simpleclouds, updatereffrad.

Added two tracers for the CCNs. Added the different tests in

initracer.F to make sure that, for example, microphys is not
used without doubleq, etc. Corrected an inconsistency in
callsedim.F, and changed the way r0 is updated. Changes
routines: callsedim, inifis, initracer, physiq, testphys1d,
tracer.h.

Added the ability to have a spatially variable density in

newsedim (same method as that used for the radius of
sedimentation). Required the addition of one input to newsedim,
which is the size of the density variable "rho". Changed
routines: callsedim, newsedim.

Added an output to aeropacity called "tauscaling", which is a

factor to convert dust_mass and dust_number to true quantities,
based on tauvis. Removed ccn and qdust from aeropacity, which
are obsolete now.

Wrote improvedcloud.F which includes all the microphysical

scheme, and connected it to the sedimentation scheme. Added and
changed routines: callsedim, physiq, growthrate, nuclea,
improvedclouds, initracer, watercloud, microphys.h.

07/11/11 == TN

Added CCN & dust tracers updates in physiq.F

Corrected a bug that can give negative CCN numbers, due to the
use of single precision values (only 6 decimals) whereas up to 10E+10
CCN can be formed or disappears...

Corrected physical bug that causes h2o_vap or h2o_ice

to be negative in improvedclouds.F.

Corrected physical bug that causes CCN & dust tracers

to be negative in improvedclouds.F when all ice sublimates and
releases dust

Added parameter contact mteta in callphys.def

Default value is still 0.95, see inifis.F

Changed tendancy computation for dust_number in improvedclouds.F

that was not the right one. Indeed, the scavenged dust_number tracer
is computed from the dust_mass one, and its tendancy before scavenging
must be taken into account to compute its scavenging's tendancy.

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