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

Last change on this file since 1266 was 1266, checked in by aslmd, 11 years ago

LMDZ.MARS
IMPORTANT CHANGE

  • Remove all reference/use of nlayermx and dimphys.h
  • Made use of automatic arrays whenever arrays are needed with dimension nlayer
  • Remove lots of obsolete reference to dimensions.h
  • Converted iono.h and param_v4.h into corresponding modules

(with embedded subroutine to allocate arrays)
(no arrays allocated if thermosphere not used)

  • Deleted param.h and put contents into module param_v4_h
  • Adapted testphys1d, newstart, etc...
  • Made DATA arrays in param_read to be initialized by subroutine

fill_data_thermos in module param_v4_h

  • Optimized computations in paramfoto_compact (twice less dlog10 calculations)
  • Checked consistency before/after modification in debug mode
  • Checked performance is not impacted (same as before)
File size: 21.2 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        alpha_lift(igcm_dust_mass)=1.e-6 !1.e-6 !Lifted mass coeff
432
433        r0_lift = reff_lift/ref_r0
434        alpha_devil(igcm_dust_number)=r3n_q*
435     &                        alpha_devil(igcm_dust_mass)/r0_lift**3
436        alpha_lift(igcm_dust_number)=r3n_q*
437     &                        alpha_lift(igcm_dust_mass)/r0_lift**3
438
439        radius(igcm_dust_mass) = reff_lift
440        radius(igcm_dust_number) = reff_lift
441
442        write(*,*) "initracer: doubleq_param reff_lift:", reff_lift
443        write(*,*) "initracer: doubleq_param nueff_lift:", nueff_lift
444        write(*,*) "initracer: doubleq_param alpha_lift:",
445     &    alpha_lift(igcm_dust_mass)
446      else
447
448       ! initialize varian, which may be used (e.g. by surfacearea)
449       ! even with conrath dust
450       nueff_lift = 0.5
451       varian=sqrt(log(1.+nueff_lift))
452
453       if (dustbin.gt.1) then
454        print*,'initracer: STOP!',
455     $   ' properties of dust need to be set in initracer !!!'
456        stop
457
458       else if (dustbin.eq.1) then
459
460c       This will be used for 1 dust particle size:
461c       ------------------------------------------
462        radius(igcm_dustbin(1))=3.e-6
463        alpha_lift(igcm_dustbin(1))=0.0e-6
464        alpha_devil(igcm_dustbin(1))=7.65e-9
465        rho_q(igcm_dustbin(1))=rho_dust
466
467       endif
468      end if    ! (doubleq)
469
470
471c     Scavenging of dust particles by H2O clouds:
472c     ------------------------------------------
473c     Initialize the two tracers used for the CCNs
474      if (water.AND.doubleq.AND.scavenging) then
475        radius(igcm_ccn_mass) = radius(igcm_dust_mass)
476        alpha_lift(igcm_ccn_mass) = 1e-30
477        alpha_devil(igcm_ccn_mass) = 1e-30
478        rho_q(igcm_ccn_mass) = rho_dust
479
480        radius(igcm_ccn_number) = radius(igcm_ccn_mass)
481        alpha_lift(igcm_ccn_number) = alpha_lift(igcm_ccn_mass)
482        alpha_devil(igcm_ccn_number) = alpha_devil(igcm_ccn_mass)
483        rho_q(igcm_ccn_number) = rho_q(igcm_ccn_mass)
484      endif ! of if (water.AND.doubleq.AND.scavenging)
485
486c     Submicron dust mode:
487c     --------------------
488
489      if (submicron) then
490        radius(igcm_dust_submicron)=0.1e-6
491        rho_q(igcm_dust_submicron)=rho_dust
492        if (doubleq) then
493c         If doubleq is also active, we use the population ratio:
494          alpha_lift(igcm_dust_submicron) =
495     &      alpha_lift(igcm_dust_number)*popratio*
496     &      rho_q(igcm_dust_submicron)*4./3.*pi*
497     &      radius(igcm_dust_submicron)**3.
498          alpha_devil(igcm_dust_submicron)=1.e-30
499        else
500          alpha_lift(igcm_dust_submicron)=1e-6
501          alpha_devil(igcm_dust_submicron)=1.e-30
502        endif ! (doubleq)
503      end if  ! (submicron)
504
505c     Initialization for water vapor
506c     ------------------------------
507      if(water) then
508         radius(igcm_h2o_vap)=0.
509         alpha_lift(igcm_h2o_vap) =0.
510         alpha_devil(igcm_h2o_vap)=0.
511         if(water.and.(nq.ge.2)) then
512           radius(igcm_h2o_ice)=3.e-6
513           rho_q(igcm_h2o_ice)=rho_ice
514           alpha_lift(igcm_h2o_ice) =0.
515           alpha_devil(igcm_h2o_ice)=0.
516         elseif(water.and.(nq.lt.2)) then
517            write(*,*) 'nq is too low : nq=', nq
518            write(*,*) 'water= ',water
519         endif
520
521      end if  ! (water)
522
523c     Output for records:
524c     ~~~~~~~~~~~~~~~~~~
525      write(*,*)
526      Write(*,*) '******** initracer : dust transport parameters :'
527      write(*,*) 'alpha_lift = ', alpha_lift
528      write(*,*) 'alpha_devil = ', alpha_devil
529      write(*,*) 'radius  = ', radius
530      if(doubleq) then
531        write(*,*) 'reff_lift (um) =  ', reff_lift
532        write(*,*) 'size distribution variance  = ', varian
533        write(*,*) 'r3n_q , ref_r0 : ', r3n_q , ref_r0
534      end if
535
536!
537!     some extra (possibly redundant) sanity checks for tracers:
538!     ---------------------------------------------------------
539
540       if (doubleq) then
541       ! verify that we indeed have dust_mass and dust_number tracers
542         if (igcm_dust_mass.eq.0) then
543           write(*,*) "initracer: error !!"
544           write(*,*) "  cannot use doubleq option without ",
545     &                "a dust_mass tracer !"
546           stop
547         endif
548         if (igcm_dust_number.eq.0) then
549           write(*,*) "initracer: error !!"
550           write(*,*) "  cannot use doubleq option without ",
551     &                "a dust_number tracer !"
552           stop
553         endif
554       endif
555
556       if ((.not.doubleq).and.(dustbin.gt.0)) then
557       ! verify that we indeed have 'dustbin' dust tracers
558         count=0
559         do iq=1,dustbin
560           if (igcm_dustbin(iq).ne.0) then
561             count=count+1
562           endif
563         enddo
564         if (count.ne.dustbin) then
565           write(*,*) "initracer: error !!"
566           write(*,*) "  dusbin is set to ",dustbin,
567     &                " but we only have the following dust tracers:"
568           do iq=1,count
569             write(*,*)"   ",trim(noms(igcm_dustbin(iq)))
570           enddo
571           stop
572         endif
573       endif
574
575       if (water) then
576       ! verify that we indeed have h2o_vap and h2o_ice tracers
577         if (igcm_h2o_vap.eq.0) then
578           write(*,*) "initracer: error !!"
579           write(*,*) "  cannot use water option without ",
580     &                "an h2o_vap tracer !"
581           stop
582         endif
583         if (igcm_h2o_ice.eq.0) then
584           write(*,*) "initracer: error !!"
585           write(*,*) "  cannot use water option without ",
586     &                "an h2o_ice tracer !"
587           stop
588         endif
589       endif
590
591       if (scavenging) then
592       ! verify that we indeed have ccn_mass and ccn_number tracers
593         if (igcm_ccn_mass.eq.0) then
594           write(*,*) "initracer: error !!"
595           write(*,*) "  cannot use scavenging option without ",
596     &                "a ccn_mass tracer !"
597           stop
598         endif
599         if (igcm_ccn_number.eq.0) then
600           write(*,*) "initracer: error !!"
601           write(*,*) "  cannot use scavenging option without ",
602     &                "a ccn_number tracer !"
603           stop
604         endif
605       endif ! of if (scavenging)
606
607       if (photochem .or. callthermos) then
608       ! verify that we indeed have the chemistry tracers
609         if (igcm_co2.eq.0) then
610           write(*,*) "initracer: error !!"
611           write(*,*) "  cannot use chemistry option without ",
612     &                "a co2 tracer !"
613         stop
614         endif
615         if (igcm_co.eq.0) then
616           write(*,*) "initracer: error !!"
617           write(*,*) "  cannot use chemistry option without ",
618     &                "a co tracer !"
619         stop
620         endif
621         if (igcm_o.eq.0) then
622           write(*,*) "initracer: error !!"
623           write(*,*) "  cannot use chemistry option without ",
624     &                "a o tracer !"
625         stop
626         endif
627         if (igcm_o1d.eq.0) then
628           write(*,*) "initracer: error !!"
629           write(*,*) "  cannot use chemistry option without ",
630     &                "a o1d tracer !"
631         stop
632         endif
633         if (igcm_o2.eq.0) then
634           write(*,*) "initracer: error !!"
635           write(*,*) "  cannot use chemistry option without ",
636     &                "an o2 tracer !"
637         stop
638         endif
639         if (igcm_o3.eq.0) then
640           write(*,*) "initracer: error !!"
641           write(*,*) "  cannot use chemistry option without ",
642     &                "an o3 tracer !"
643         stop
644         endif
645         if (igcm_h.eq.0) then
646           write(*,*) "initracer: error !!"
647           write(*,*) "  cannot use chemistry option without ",
648     &                "a h tracer !"
649         stop
650         endif
651         if (igcm_h2.eq.0) then
652           write(*,*) "initracer: error !!"
653           write(*,*) "  cannot use chemistry option without ",
654     &                "a h2 tracer !"
655         stop
656         endif
657         if (igcm_oh.eq.0) then
658           write(*,*) "initracer: error !!"
659           write(*,*) "  cannot use chemistry option without ",
660     &                "an oh tracer !"
661         stop
662         endif
663         if (igcm_ho2.eq.0) then
664           write(*,*) "initracer: error !!"
665           write(*,*) "  cannot use chemistry option without ",
666     &                "a ho2 tracer !"
667         stop
668         endif
669         if (igcm_h2o2.eq.0) then
670           write(*,*) "initracer: error !!"
671           write(*,*) "  cannot use chemistry option without ",
672     &                "a h2o2 tracer !"
673         stop
674         endif
675         if (igcm_n2.eq.0) then
676           write(*,*) "initracer: error !!"
677           write(*,*) "  cannot use chemistry option without ",
678     &                "a n2 tracer !"
679         stop
680         endif
681         if (igcm_ar.eq.0) then
682           write(*,*) "initracer: error !!"
683           write(*,*) "  cannot use chemistry option without ",
684     &                "an ar tracer !"
685         stop
686         endif
687       endif ! of if (photochem .or. callthermos)
688
689      end
Note: See TracBrowser for help on using the repository browser.