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

Last change on this file since 286 was 285, checked in by aslmd, 14 years ago

08/09/11 == AS

LMDZ.MARS + MESOSCALE.
---> Setting up a more realistic water ice source at the poles (notably outliers)

surfini.F ?
Main changes and bug fixes

  • reference to comcstfi.h was wrong. big problem because e.g. pi was not known.
  • commented about a problem to be fixed, due to surfini being called before initracer.
  • MESOSCALE: put the mesoscale north cap definition into a precompiling flag #MESOSCALE

for the moment: if [alb_mean_TES > 0.26 and lat > 70] then outliers
(previously done in meso_inc_caps.F)

inifis.F ?
Just changed a comment with wrong formatting

--> below, only MESOSCALE

soil.F ?
if somewhere IT > IT_outliers, then makes it = IT_outliers

physiq.F ?
meso_inc/meso_inc_caps.F ?
meso_inc/meso_inc_ini.F ?
meso_inc_caps no longer called. keep for reference for the moment.

meso_inc/meso_inc_var.F ?
deleted lines with *_lim variables, now useless

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