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

Last change on this file since 1617 was 1617, checked in by jaudouard, 8 years ago

Added modifications for CO2 clouds scheme in physiq_mod.F and added several routines and variables for CO2 microphysics. October 2016 Joachim Audouard

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