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

Last change on this file since 1660 was 1660, checked in by emillour, 8 years ago

Mars GCM:

  • Added possibility to run with an Helium "he" tracer (to be initialized at constant value of 3.6e-7 kg/kg_air, i.e. the 4ppm of Krasnopolsky 1996 EUVE satellite, using newstart).
  • corrected case for CH4 in aeronomars/photochemistry.F (was using undefined indexes when there is no CH4).
  • updated aki/cpi coefficients for Argon used to compute mean atmospheric Cp and thermal conductivity in aeronomars/concentrations.F

JYC+EM

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