source: trunk/LMDZ.MARS/libf/phymars/initracer.F @ 1467

Last change on this file since 1467 was 1455, checked in by aslmd, 10 years ago

MESOSCALE. can now use same callphys than GCM. necessary changes are in run.def. modified initracer to be compliant with lifting differences. and also made GCM 29 levels by default.

File size: 22.4 KB
Line 
1      SUBROUTINE initracer(ngrid,nq,qsurf)
2
3#ifndef MESOSCALE
4       use infotrac, only: tname
5#endif
6       use tracer_mod
7       USE comcstfi_h
8       IMPLICIT NONE
9c=======================================================================
10c   subject:
11c   --------
12c   Initialization related to tracer
13c   (transported dust, water, chemical species, ice...)
14c
15c   Name of the tracer
16c
17c   Test of dimension :
18c   Initialize tracer related data in tracer_mod, using tracer names provided
19c   by the dynamics in "infotrac"
20c
21c
22c   author: F.Forget
23c   ------
24c    Modifs: Franck Montmessin, Sebastien Lebonnois (june 2003)
25c            Ehouarn Millour (oct. 2008) identify tracers by their names
26c=======================================================================
27
28
29#include "callkeys.h"
30
31      integer,intent(in) :: ngrid ! number of atmospheric columns
32      integer,intent(in) :: nq ! number of tracers
33      real,intent(out) :: qsurf(ngrid,nq) ! tracer on surface (e.g.  kg.m-2)
34
35      integer iq,ig,count
36      real r0_lift , reff_lift, nueff_lift
37c     Ratio of small over large dust particles (used when both
38c       doubleq and the submicron mode are active); In Montmessin
39c       et al. (2002), a value of 25 has been deduced;
40      real, parameter :: popratio = 25.
41      character(len=20) :: txt ! to store some text
42
43c-----------------------------------------------------------------------
44c  radius(nq)      ! aerosol particle radius (m)
45c  rho_q(nq)       ! tracer densities (kg.m-3)
46c  alpha_lift(nq)  ! saltation vertical flux/horiz flux ratio (m-1)
47c  alpha_devil(nq) ! lifting coeeficient by dust devil
48c  rho_dust          ! Mars dust density
49c  rho_ice           ! Water ice density
50c  nuice_ref         ! Effective variance nueff of the
51c                    !   water-ice size distributions
52c  doubleq           ! if method with mass (iq=1) and number(iq=2) mixing ratio
53c  varian            ! Characteristic variance of log-normal distribution
54c-----------------------------------------------------------------------
55
56! Initialization: allocate arrays in tracer_mod
57      allocate(mmol(nq))
58      allocate(radius(nq))
59      allocate(rho_q(nq))
60      allocate(alpha_lift(nq))
61      allocate(alpha_devil(nq))
62      allocate(igcm_dustbin(nq))
63      allocate(nqdust(nq))
64
65#ifndef MESOSCALE
66      allocate(noms(nq))
67! Initialization: get tracer names from the dynamics and check if we are
68!                 using 'old' tracer convention ('q01',q02',...)
69!                 or new convention (full tracer names)
70      ! check if tracers have 'old' names
71      count=0
72      do iq=1,nq
73        txt=" "
74        write(txt,'(a1,i2.2)') 'q',iq
75        if (txt.eq.tname(iq)) then
76          count=count+1
77        endif
78      enddo ! of do iq=1,nq
79     
80      if (count.eq.nq) then
81        write(*,*) "initracer: tracers seem to follow old naming ",
82     &             "convention (q01,q02,...)"
83        write(*,*) "you should run newstart to rename them"
84        stop
85      endif
86
87      ! copy tracer names from dynamics
88      do iq=1,nq
89        noms(iq)=tname(iq)
90      enddo
91#endif
92
93c------------------------------------------------------------
94c         NAME and molar mass of the tracer
95c------------------------------------------------------------
96   
97! Identify tracers by their names: (and set corresponding values of mmol)
98      ! 0. initialize tracer indexes to zero:
99      igcm_dustbin(1:nq)=0
100
101      igcm_dust_mass=0
102      igcm_dust_number=0
103      igcm_ccn_mass=0
104      igcm_ccn_number=0
105      igcm_dust_submicron=0
106      igcm_h2o_vap=0
107      igcm_h2o_ice=0
108      igcm_co2=0
109      igcm_co=0
110      igcm_o=0
111      igcm_o1d=0
112      igcm_o2=0
113      igcm_o3=0
114      igcm_h=0
115      igcm_h2=0
116      igcm_oh=0
117      igcm_ho2=0
118      igcm_h2o2=0
119      igcm_ch4=0
120      igcm_n2=0
121      igcm_ar=0
122      igcm_ar_n2=0
123      igcm_n=0
124      igcm_no=0
125      igcm_no2=0
126      igcm_n2d=0
127      igcm_co2plus=0
128      igcm_oplus=0
129      igcm_o2plus=0
130      igcm_coplus=0
131      igcm_cplus=0
132      igcm_nplus=0
133      igcm_noplus=0
134      igcm_n2plus=0
135      igcm_hplus=0
136      igcm_hco2plus=0
137      igcm_elec=0
138
139      ! 1. find dust tracers
140      count=0
141      if (dustbin.gt.0) then
142        do iq=1,nq
143          txt=" "
144          write(txt,'(a4,i2.2)')'dust',count+1
145          if (noms(iq).eq.txt) then
146            count=count+1
147            igcm_dustbin(count)=iq
148            mmol(iq)=100.
149          endif
150        enddo !do iq=1,nq
151      endif ! of if (dustbin.gt.0)
152      if (doubleq) then
153        do iq=1,nq
154          if (noms(iq).eq."dust_mass") then
155            igcm_dust_mass=iq
156            count=count+1
157          endif
158          if (noms(iq).eq."dust_number") then
159            igcm_dust_number=iq
160            count=count+1
161          endif
162        enddo
163      endif ! of if (doubleq)
164      if (microphys) then
165        do iq=1,nq
166          if (noms(iq).eq."ccn_mass") then
167            igcm_ccn_mass=iq
168            count=count+1
169          endif
170          if (noms(iq).eq."ccn_number") then
171            igcm_ccn_number=iq
172            count=count+1
173          endif
174        enddo
175      endif ! of if (microphys)
176      if (submicron) then
177        do iq=1,nq
178          if (noms(iq).eq."dust_submicron") then
179            igcm_dust_submicron=iq
180            mmol(iq)=100.
181            count=count+1
182          endif
183        enddo
184      endif ! of if (submicron)
185      ! 2. find chemistry and water tracers
186      do iq=1,nq
187        if (noms(iq).eq."co2") then
188          igcm_co2=iq
189          mmol(igcm_co2)=44.
190          count=count+1
191        endif
192        if (noms(iq).eq."co") then
193          igcm_co=iq
194          mmol(igcm_co)=28.
195          count=count+1
196        endif
197        if (noms(iq).eq."o") then
198          igcm_o=iq
199          mmol(igcm_o)=16.
200          count=count+1
201        endif
202        if (noms(iq).eq."o1d") then
203          igcm_o1d=iq
204          mmol(igcm_o1d)=16.
205          count=count+1
206        endif
207        if (noms(iq).eq."o2") then
208          igcm_o2=iq
209          mmol(igcm_o2)=32.
210          count=count+1
211        endif
212        if (noms(iq).eq."o3") then
213          igcm_o3=iq
214          mmol(igcm_o3)=48.
215          count=count+1
216        endif
217        if (noms(iq).eq."h") then
218          igcm_h=iq
219          mmol(igcm_h)=1.
220          count=count+1
221        endif
222        if (noms(iq).eq."h2") then
223          igcm_h2=iq
224          mmol(igcm_h2)=2.
225          count=count+1
226        endif
227        if (noms(iq).eq."oh") then
228          igcm_oh=iq
229          mmol(igcm_oh)=17.
230          count=count+1
231        endif
232        if (noms(iq).eq."ho2") then
233          igcm_ho2=iq
234          mmol(igcm_ho2)=33.
235          count=count+1
236        endif
237        if (noms(iq).eq."h2o2") then
238          igcm_h2o2=iq
239          mmol(igcm_h2o2)=34.
240          count=count+1
241        endif
242        if (noms(iq).eq."n2") then
243          igcm_n2=iq
244          mmol(igcm_n2)=28.
245          count=count+1
246        endif
247        if (noms(iq).eq."ch4") then
248          igcm_ch4=iq
249          mmol(igcm_ch4)=16.
250          count=count+1
251        endif
252        if (noms(iq).eq."ar") then
253          igcm_ar=iq
254          mmol(igcm_ar)=40.
255          count=count+1
256        endif
257        if (noms(iq).eq."n") then
258          igcm_n=iq
259          mmol(igcm_n)=14.
260          count=count+1
261        endif
262        if (noms(iq).eq."no") then
263          igcm_no=iq
264          mmol(igcm_no)=30.
265          count=count+1
266        endif
267        if (noms(iq).eq."no2") then
268          igcm_no2=iq
269          mmol(igcm_no2)=46.
270          count=count+1
271        endif
272        if (noms(iq).eq."n2d") then
273          igcm_n2d=iq
274          mmol(igcm_n2d)=28.
275          count=count+1
276        endif
277        if (noms(iq).eq."co2plus") then
278          igcm_co2plus=iq
279          mmol(igcm_co2plus)=44.
280          count=count+1
281        endif
282        if (noms(iq).eq."oplus") then
283          igcm_oplus=iq
284          mmol(igcm_oplus)=16.
285          count=count+1
286        endif
287        if (noms(iq).eq."o2plus") then
288          igcm_o2plus=iq
289          mmol(igcm_o2plus)=32.
290          count=count+1
291        endif
292        if (noms(iq).eq."coplus") then
293          igcm_coplus=iq
294          mmol(igcm_coplus)=28.
295          count=count+1
296        endif
297        if (noms(iq).eq."cplus") then
298          igcm_cplus=iq
299          mmol(igcm_cplus)=12.
300          count=count+1
301        endif
302        if (noms(iq).eq."nplus") then
303          igcm_nplus=iq
304          mmol(igcm_nplus)=14.
305          count=count+1
306        endif
307        if (noms(iq).eq."noplus") then
308          igcm_noplus=iq
309          mmol(igcm_noplus)=30.
310          count=count+1
311        endif
312        if (noms(iq).eq."n2plus") then
313          igcm_n2plus=iq
314          mmol(igcm_n2plus)=28.
315          count=count+1
316        endif
317        if (noms(iq).eq."hplus") then
318          igcm_hplus=iq
319          mmol(igcm_hplus)=1.
320          count=count+1
321        endif
322        if (noms(iq).eq."hco2plus") then
323          igcm_hco2plus=iq
324          mmol(igcm_hco2plus)=45.
325          count=count+1
326        endif
327        if (noms(iq).eq."elec") then
328          igcm_elec=iq
329          mmol(igcm_elec)=1./1822.89
330          count=count+1
331        endif
332        if (noms(iq).eq."h2o_vap") then
333          igcm_h2o_vap=iq
334          mmol(igcm_h2o_vap)=18.
335          count=count+1
336        endif
337        if (noms(iq).eq."h2o_ice") then
338          igcm_h2o_ice=iq
339          mmol(igcm_h2o_ice)=18.
340          count=count+1
341        endif
342        ! Other stuff: e.g. for simulations using co2 + neutral gaz
343        if (noms(iq).eq."Ar_N2") then
344          igcm_ar_n2=iq
345          mmol(igcm_ar_n2)=30.
346          count=count+1
347        endif
348
349      enddo ! of do iq=1,nq
350     
351      ! check that we identified all tracers:
352      if (count.ne.nq) then
353        write(*,*) "initracer: found only ",count," tracers"
354        write(*,*) "               expected ",nq
355        do iq=1,count
356          write(*,*)'      ',iq,' ',trim(noms(iq))
357        enddo
358        stop
359      else
360        write(*,*) "initracer: found all expected tracers, namely:"
361        do iq=1,nq
362          write(*,*)'      ',iq,' ',trim(noms(iq))
363        enddo
364      endif
365
366      ! if water cycle but iceparty=.false., there will nevertheless be
367      ! water ice at the surface (iceparty is not used anymore, but this
368      ! part is still relevant, as we want to stay compatible with the
369      ! older versions).
370      if (water.and.(igcm_h2o_ice.eq.0)) then
371        igcm_h2o_ice=igcm_h2o_vap ! so that qsurf(i_h2o_ice) is identified
372                                  ! even though there is no q(i_h2o_ice)
373      else
374       ! surface ice qsurf(i_h2o_ice) was loaded twice by phyetat0,
375       ! as qsurf(i_h2o_vap) & as qsurf(i_h2o_ice), so to be clean:
376       if (igcm_h2o_vap.ne.0) then
377         qsurf(1:ngrid,igcm_h2o_vap)=0
378       endif
379      endif
380
381c------------------------------------------------------------
382c     Initialize tracers .... (in tracer_mod)
383c------------------------------------------------------------
384      ! start by setting everything to (default) zero
385      rho_q(1:nq)=0     ! tracer density (kg.m-3)
386      radius(1:nq)=0.   ! tracer particle radius (m)
387      alpha_lift(1:nq) =0.  ! tracer saltation vertical flux/horiz flux ratio (m-1)
388      alpha_devil(1:nq)=0.  ! tracer lifting coefficient by dust devils
389
390
391      ! some reference values
392      rho_dust=2500.  ! Mars dust density (kg.m-3)
393      rho_ice=920.    ! Water ice density (kg.m-3)
394      nuice_ref=0.1   ! Effective variance nueff of the
395                      ! water-ice size distribution
396      !!!nuice_sed=0.45   ! Sedimentation effective variance
397                      ! of the water-ice size distribution
398
399      if (doubleq) then
400c       "doubleq" technique
401c       -------------------
402c      (transport of mass and number mixing ratio)
403c       iq=1: Q mass mixing ratio, iq=2: N number mixing ratio
404
405        if( (nq.lt.2).or.(water.and.(nq.lt.4)) ) then
406          write(*,*)'initracer: nq is too low : nq=', nq
407          write(*,*)'water= ',water,' doubleq= ',doubleq   
408        end if
409
410        nueff_lift = 0.5
411        varian=sqrt(log(1.+nueff_lift))
412
413        rho_q(igcm_dust_mass)=rho_dust
414        rho_q(igcm_dust_number)=rho_dust
415
416c       Intermediate calcul for computing geometric mean radius r0
417c       as a function of mass and number mixing ratio Q and N
418c       (r0 = (r3n_q * Q/ N)^(1/3))
419        r3n_q = exp(-4.5*varian**2)*(3./4.)/(pi*rho_dust)
420
421c       Intermediate calcul for computing effective radius reff
422c       from geometric mean radius r0
423c       (reff = ref_r0 * r0)
424        ref_r0 = exp(2.5*varian**2)
425       
426c       lifted dust :
427c       '''''''''''
428        reff_lift = 3.0e-6 !3.e-6 !Effective radius of lifted dust (m)
429        alpha_devil(igcm_dust_mass)=9.e-9   !  dust devil lift mass coeff
430c       alpha_lift(igcm_dust_mass)=3.0e-15  !  Lifted mass coeff
431
432!! default lifting settings
433!! -- GCM: alpha_lift not zero because large-scale lifting by default
434!! -- MESOSCALE: alpha_lift zero because no lifting at all in mesoscale by default
435#ifdef MESOSCALE
436        alpha_lift(igcm_dust_mass)=0.0
437#else
438        alpha_lift(igcm_dust_mass)=1.e-6 !1.e-6 !Lifted mass coeff
439#endif
440
441        r0_lift = reff_lift/ref_r0
442        alpha_devil(igcm_dust_number)=r3n_q*
443     &                        alpha_devil(igcm_dust_mass)/r0_lift**3
444        alpha_lift(igcm_dust_number)=r3n_q*
445     &                        alpha_lift(igcm_dust_mass)/r0_lift**3
446
447        radius(igcm_dust_mass) = reff_lift
448        radius(igcm_dust_number) = reff_lift
449
450        write(*,*) "initracer: doubleq_param reff_lift:", reff_lift
451        write(*,*) "initracer: doubleq_param nueff_lift:", nueff_lift
452        write(*,*) "initracer: doubleq_param alpha_lift:",
453     &    alpha_lift(igcm_dust_mass)
454      else
455
456       ! initialize varian, which may be used (e.g. by surfacearea)
457       ! even with conrath dust
458       nueff_lift = 0.5
459       varian=sqrt(log(1.+nueff_lift))
460
461       if (dustbin.gt.1) then
462        print*,'initracer: STOP!',
463     $   ' properties of dust need to be set in initracer !!!'
464        stop
465
466       else if (dustbin.eq.1) then
467
468c       This will be used for 1 dust particle size:
469c       ------------------------------------------
470        radius(igcm_dustbin(1))=3.e-6
471        alpha_lift(igcm_dustbin(1))=0.0e-6
472        alpha_devil(igcm_dustbin(1))=7.65e-9
473        rho_q(igcm_dustbin(1))=rho_dust
474
475       endif
476      end if    ! (doubleq)
477
478
479c     Scavenging of dust particles by H2O clouds:
480c     ------------------------------------------
481c     Initialize the two tracers used for the CCNs
482      if (water.AND.doubleq.AND.scavenging) then
483        radius(igcm_ccn_mass) = radius(igcm_dust_mass)
484        alpha_lift(igcm_ccn_mass) = 1e-30
485        alpha_devil(igcm_ccn_mass) = 1e-30
486        rho_q(igcm_ccn_mass) = rho_dust
487
488        radius(igcm_ccn_number) = radius(igcm_ccn_mass)
489        alpha_lift(igcm_ccn_number) = alpha_lift(igcm_ccn_mass)
490        alpha_devil(igcm_ccn_number) = alpha_devil(igcm_ccn_mass)
491        rho_q(igcm_ccn_number) = rho_q(igcm_ccn_mass)
492      endif ! of if (water.AND.doubleq.AND.scavenging)
493
494c     Submicron dust mode:
495c     --------------------
496
497      if (submicron) then
498        radius(igcm_dust_submicron)=0.1e-6
499        rho_q(igcm_dust_submicron)=rho_dust
500        if (doubleq) then
501c         If doubleq is also active, we use the population ratio:
502          alpha_lift(igcm_dust_submicron) =
503     &      alpha_lift(igcm_dust_number)*popratio*
504     &      rho_q(igcm_dust_submicron)*4./3.*pi*
505     &      radius(igcm_dust_submicron)**3.
506          alpha_devil(igcm_dust_submicron)=1.e-30
507        else
508          alpha_lift(igcm_dust_submicron)=1e-6
509          alpha_devil(igcm_dust_submicron)=1.e-30
510        endif ! (doubleq)
511      end if  ! (submicron)
512
513c     Initialization for water vapor
514c     ------------------------------
515      if(water) then
516         radius(igcm_h2o_vap)=0.
517         alpha_lift(igcm_h2o_vap) =0.
518         alpha_devil(igcm_h2o_vap)=0.
519         if(water.and.(nq.ge.2)) then
520           radius(igcm_h2o_ice)=3.e-6
521           rho_q(igcm_h2o_ice)=rho_ice
522           alpha_lift(igcm_h2o_ice) =0.
523           alpha_devil(igcm_h2o_ice)=0.
524         elseif(water.and.(nq.lt.2)) then
525            write(*,*) 'nq is too low : nq=', nq
526            write(*,*) 'water= ',water
527         endif
528
529      end if  ! (water)
530
531c     Output for records:
532c     ~~~~~~~~~~~~~~~~~~
533      write(*,*)
534      Write(*,*) '******** initracer : dust transport parameters :'
535      write(*,*) 'alpha_lift = ', alpha_lift
536      write(*,*) 'alpha_devil = ', alpha_devil
537      write(*,*) 'radius  = ', radius
538      if(doubleq) then
539        write(*,*) 'reff_lift (um) =  ', reff_lift
540        write(*,*) 'size distribution variance  = ', varian
541        write(*,*) 'r3n_q , ref_r0 : ', r3n_q , ref_r0
542      end if
543
544!
545!     some extra (possibly redundant) sanity checks for tracers:
546!     ---------------------------------------------------------
547
548       if (doubleq) then
549       ! verify that we indeed have dust_mass and dust_number tracers
550         if (igcm_dust_mass.eq.0) then
551           write(*,*) "initracer: error !!"
552           write(*,*) "  cannot use doubleq option without ",
553     &                "a dust_mass tracer !"
554           stop
555         endif
556         if (igcm_dust_number.eq.0) then
557           write(*,*) "initracer: error !!"
558           write(*,*) "  cannot use doubleq option without ",
559     &                "a dust_number tracer !"
560           stop
561         endif
562       endif
563
564       if ((.not.doubleq).and.(dustbin.gt.0)) then
565       ! verify that we indeed have 'dustbin' dust tracers
566         count=0
567         do iq=1,dustbin
568           if (igcm_dustbin(iq).ne.0) then
569             count=count+1
570           endif
571         enddo
572         if (count.ne.dustbin) then
573           write(*,*) "initracer: error !!"
574           write(*,*) "  dusbin is set to ",dustbin,
575     &                " but we only have the following dust tracers:"
576           do iq=1,count
577             write(*,*)"   ",trim(noms(igcm_dustbin(iq)))
578           enddo
579           stop
580         endif
581       endif
582
583       if (water) then
584       ! verify that we indeed have h2o_vap and h2o_ice tracers
585         if (igcm_h2o_vap.eq.0) then
586           write(*,*) "initracer: error !!"
587           write(*,*) "  cannot use water option without ",
588     &                "an h2o_vap tracer !"
589           stop
590         endif
591         if (igcm_h2o_ice.eq.0) then
592           write(*,*) "initracer: error !!"
593           write(*,*) "  cannot use water option without ",
594     &                "an h2o_ice tracer !"
595           stop
596         endif
597       endif
598
599       if (callnlte) then ! NLTE requirements
600         if (nltemodel.ge.1) then
601           ! check that co2, co, o and n2 tracers are available
602           if (igcm_co2.eq.0) then
603             write(*,*) "initracer: error !!"
604             write(*,*) "  with nltemodel>0, we need the co2 tracer!"
605             stop
606           endif
607           if (igcm_co.eq.0) then
608             write(*,*) "initracer: error !!"
609             write(*,*) "  with nltemodel>0, we need the co tracer!"
610             stop
611           endif
612           if (igcm_o.eq.0) then
613             write(*,*) "initracer: error !!"
614             write(*,*) "  with nltemodel>0, we need the o tracer!"
615             stop
616           endif
617           if (igcm_n2.eq.0) then
618             write(*,*) "initracer: error !!"
619             write(*,*) "  with nltemodel>0, we need the n2 tracer!"
620             stop
621           endif
622         endif
623       endif
624
625       if (scavenging) then
626       ! verify that we indeed have ccn_mass and ccn_number tracers
627         if (igcm_ccn_mass.eq.0) then
628           write(*,*) "initracer: error !!"
629           write(*,*) "  cannot use scavenging option without ",
630     &                "a ccn_mass tracer !"
631           stop
632         endif
633         if (igcm_ccn_number.eq.0) then
634           write(*,*) "initracer: error !!"
635           write(*,*) "  cannot use scavenging option without ",
636     &                "a ccn_number tracer !"
637           stop
638         endif
639       endif ! of if (scavenging)
640
641       if (photochem .or. callthermos) then
642       ! verify that we indeed have the chemistry tracers
643         if (igcm_co2.eq.0) then
644           write(*,*) "initracer: error !!"
645           write(*,*) "  cannot use chemistry option without ",
646     &                "a co2 tracer !"
647         stop
648         endif
649         if (igcm_co.eq.0) then
650           write(*,*) "initracer: error !!"
651           write(*,*) "  cannot use chemistry option without ",
652     &                "a co tracer !"
653         stop
654         endif
655         if (igcm_o.eq.0) then
656           write(*,*) "initracer: error !!"
657           write(*,*) "  cannot use chemistry option without ",
658     &                "a o tracer !"
659         stop
660         endif
661         if (igcm_o1d.eq.0) then
662           write(*,*) "initracer: error !!"
663           write(*,*) "  cannot use chemistry option without ",
664     &                "a o1d tracer !"
665         stop
666         endif
667         if (igcm_o2.eq.0) then
668           write(*,*) "initracer: error !!"
669           write(*,*) "  cannot use chemistry option without ",
670     &                "an o2 tracer !"
671         stop
672         endif
673         if (igcm_o3.eq.0) then
674           write(*,*) "initracer: error !!"
675           write(*,*) "  cannot use chemistry option without ",
676     &                "an o3 tracer !"
677         stop
678         endif
679         if (igcm_h.eq.0) then
680           write(*,*) "initracer: error !!"
681           write(*,*) "  cannot use chemistry option without ",
682     &                "a h tracer !"
683         stop
684         endif
685         if (igcm_h2.eq.0) then
686           write(*,*) "initracer: error !!"
687           write(*,*) "  cannot use chemistry option without ",
688     &                "a h2 tracer !"
689         stop
690         endif
691         if (igcm_oh.eq.0) then
692           write(*,*) "initracer: error !!"
693           write(*,*) "  cannot use chemistry option without ",
694     &                "an oh tracer !"
695         stop
696         endif
697         if (igcm_ho2.eq.0) then
698           write(*,*) "initracer: error !!"
699           write(*,*) "  cannot use chemistry option without ",
700     &                "a ho2 tracer !"
701         stop
702         endif
703         if (igcm_h2o2.eq.0) then
704           write(*,*) "initracer: error !!"
705           write(*,*) "  cannot use chemistry option without ",
706     &                "a h2o2 tracer !"
707         stop
708         endif
709         if (igcm_n2.eq.0) then
710           write(*,*) "initracer: error !!"
711           write(*,*) "  cannot use chemistry option without ",
712     &                "a n2 tracer !"
713         stop
714         endif
715         if (igcm_ar.eq.0) then
716           write(*,*) "initracer: error !!"
717           write(*,*) "  cannot use chemistry option without ",
718     &                "an ar tracer !"
719         stop
720         endif
721       endif ! of if (photochem .or. callthermos)
722
723      end
Note: See TracBrowser for help on using the repository browser.