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

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

MESOSCALE
LMDZ.MARS

--> Performed the necessary modifications for dynamic tracers

to work with the mesoscale model (new physics).

--> Added precompiling flag MESOSCALE around pressure modifications

done in revision 883. This makes the mesoscale model become crazy.

--> Added an option -e in makemeso to erase a configuration and start over.

NOTE
--> not sure recent versions (rev>1000) are compliant with nesting compilation.
--> use mesoscale model + new physics with caution. still not stabilized.

File size: 21.5 KB
Line 
1      SUBROUTINE initracer(ngrid,nq,qsurf,co2ice)
2
3#ifndef MESOSCALE
4       use infotrac, only: tnom
5#endif
6       use tracer_mod
7       IMPLICIT NONE
8c=======================================================================
9c   subject:
10c   --------
11c   Initialization related to tracer
12c   (transported dust, water, chemical species, ice...)
13c
14c   Name of the tracer
15c
16c   Test of dimension :
17c   Initialize tracer related data in tracer_mod, using tracer names provided
18c   by the dynamics in "infotrac"
19c
20c
21c   author: F.Forget
22c   ------
23c    Modifs: Franck Montmessin, Sebastien Lebonnois (june 2003)
24c            Ehouarn Millour (oct. 2008) identify tracers by their names
25c=======================================================================
26
27
28#include "dimensions.h"
29#include "dimphys.h"
30#include "comcstfi.h"
31#include "callkeys.h"
32!#include "tracer.h"
33!#include "advtrac.h"
34#include "comgeomfi.h"
35
36#include "surfdat.h"
37
38      integer,intent(in) :: ngrid ! number of atmospheric columns
39      integer,intent(in) :: nq ! number of tracers
40      real,intent(out) :: qsurf(ngrid,nq) ! tracer on surface (e.g.  kg.m-2)
41      real,intent(out) :: co2ice(ngrid) ! co2 ice mass on surface (e.g.  kg.m-2)
42
43      integer iq,ig,count
44      real r0_lift , reff_lift, nueff_lift
45c     Ratio of small over large dust particles (used when both
46c       doubleq and the submicron mode are active); In Montmessin
47c       et al. (2002), a value of 25 has been deduced;
48      real, parameter :: popratio = 25.
49      character(len=20) :: txt ! to store some text
50
51c-----------------------------------------------------------------------
52c  radius(nq)      ! aerosol particle radius (m)
53c  rho_q(nq)       ! tracer densities (kg.m-3)
54c  alpha_lift(nq)  ! saltation vertical flux/horiz flux ratio (m-1)
55c  alpha_devil(nq) ! lifting coeeficient by dust devil
56c  rho_dust          ! Mars dust density
57c  rho_ice           ! Water ice density
58c  nuice_ref         ! Effective variance nueff of the
59c                    !   water-ice size distributions
60c  doubleq           ! if method with mass (iq=1) and number(iq=2) mixing ratio
61c  varian            ! Characteristic variance of log-normal distribution
62c-----------------------------------------------------------------------
63
64! Initialization: allocate arrays in tracer_mod
65      allocate(mmol(nq))
66      allocate(radius(nq))
67      allocate(rho_q(nq))
68      allocate(alpha_lift(nq))
69      allocate(alpha_devil(nq))
70      allocate(dryness(ngridmx))
71      allocate(igcm_dustbin(nq))
72
73#ifndef MESOSCALE
74      allocate(noms(nq))
75! Initialization: get tracer names from the dynamics and check if we are
76!                 using 'old' tracer convention ('q01',q02',...)
77!                 or new convention (full tracer names)
78      ! check if tracers have 'old' names
79      count=0
80      do iq=1,nq
81        txt=" "
82        write(txt,'(a1,i2.2)') 'q',iq
83        if (txt.eq.tnom(iq)) then
84          count=count+1
85        endif
86      enddo ! of do iq=1,nq
87     
88      if (count.eq.nq) then
89        write(*,*) "initracer: tracers seem to follow old naming ",
90     &             "convention (q01,q02,...)"
91        write(*,*) "you should run newstart to rename them"
92        stop
93      endif
94
95      ! copy tracer names from dynamics
96      do iq=1,nq
97        noms(iq)=tnom(iq)
98      enddo
99#endif
100
101c------------------------------------------------------------
102c         NAME and molar mass of the tracer
103c------------------------------------------------------------
104   
105! Identify tracers by their names: (and set corresponding values of mmol)
106      ! 0. initialize tracer indexes to zero:
107      igcm_dustbin(1:nq)=0
108
109      igcm_dust_mass=0
110      igcm_dust_number=0
111      igcm_ccn_mass=0
112      igcm_ccn_number=0
113      igcm_dust_submicron=0
114      igcm_h2o_vap=0
115      igcm_h2o_ice=0
116      igcm_co2=0
117      igcm_co=0
118      igcm_o=0
119      igcm_o1d=0
120      igcm_o2=0
121      igcm_o3=0
122      igcm_h=0
123      igcm_h2=0
124      igcm_oh=0
125      igcm_ho2=0
126      igcm_h2o2=0
127      igcm_ch4=0
128      igcm_n2=0
129      igcm_ar=0
130      igcm_ar_n2=0
131      igcm_n=0
132      igcm_no=0
133      igcm_no2=0
134      igcm_n2d=0
135      igcm_co2plus=0
136      igcm_oplus=0
137      igcm_o2plus=0
138      igcm_coplus=0
139      igcm_cplus=0
140      igcm_nplus=0
141      igcm_noplus=0
142      igcm_n2plus=0
143      igcm_hplus=0
144      igcm_hco2plus=0
145      igcm_elec=0
146
147      ! 1. find dust tracers
148      count=0
149      if (dustbin.gt.0) then
150        do iq=1,nq
151          txt=" "
152          write(txt,'(a4,i2.2)')'dust',count+1
153          if (noms(iq).eq.txt) then
154            count=count+1
155            igcm_dustbin(count)=iq
156            mmol(iq)=100.
157          endif
158        enddo !do iq=1,nq
159      endif ! of if (dustbin.gt.0)
160      if (doubleq) then
161        do iq=1,nq
162          if (noms(iq).eq."dust_mass") then
163            igcm_dust_mass=iq
164            count=count+1
165          endif
166          if (noms(iq).eq."dust_number") then
167            igcm_dust_number=iq
168            count=count+1
169          endif
170        enddo
171      endif ! of if (doubleq)
172      if (microphys) then
173        do iq=1,nq
174          if (noms(iq).eq."ccn_mass") then
175            igcm_ccn_mass=iq
176            count=count+1
177          endif
178          if (noms(iq).eq."ccn_number") then
179            igcm_ccn_number=iq
180            count=count+1
181          endif
182        enddo
183      endif ! of if (microphys)
184      if (submicron) then
185        do iq=1,nq
186          if (noms(iq).eq."dust_submicron") then
187            igcm_dust_submicron=iq
188            mmol(iq)=100.
189            count=count+1
190          endif
191        enddo
192      endif ! of if (submicron)
193      ! 2. find chemistry and water tracers
194      do iq=1,nq
195        if (noms(iq).eq."co2") then
196          igcm_co2=iq
197          mmol(igcm_co2)=44.
198          count=count+1
199        endif
200        if (noms(iq).eq."co") then
201          igcm_co=iq
202          mmol(igcm_co)=28.
203          count=count+1
204        endif
205        if (noms(iq).eq."o") then
206          igcm_o=iq
207          mmol(igcm_o)=16.
208          count=count+1
209        endif
210        if (noms(iq).eq."o1d") then
211          igcm_o1d=iq
212          mmol(igcm_o1d)=16.
213          count=count+1
214        endif
215        if (noms(iq).eq."o2") then
216          igcm_o2=iq
217          mmol(igcm_o2)=32.
218          count=count+1
219        endif
220        if (noms(iq).eq."o3") then
221          igcm_o3=iq
222          mmol(igcm_o3)=48.
223          count=count+1
224        endif
225        if (noms(iq).eq."h") then
226          igcm_h=iq
227          mmol(igcm_h)=1.
228          count=count+1
229        endif
230        if (noms(iq).eq."h2") then
231          igcm_h2=iq
232          mmol(igcm_h2)=2.
233          count=count+1
234        endif
235        if (noms(iq).eq."oh") then
236          igcm_oh=iq
237          mmol(igcm_oh)=17.
238          count=count+1
239        endif
240        if (noms(iq).eq."ho2") then
241          igcm_ho2=iq
242          mmol(igcm_ho2)=33.
243          count=count+1
244        endif
245        if (noms(iq).eq."h2o2") then
246          igcm_h2o2=iq
247          mmol(igcm_h2o2)=34.
248          count=count+1
249        endif
250        if (noms(iq).eq."n2") then
251          igcm_n2=iq
252          mmol(igcm_n2)=28.
253          count=count+1
254        endif
255        if (noms(iq).eq."ch4") then
256          igcm_ch4=iq
257          mmol(igcm_ch4)=16.
258          count=count+1
259        endif
260        if (noms(iq).eq."ar") then
261          igcm_ar=iq
262          mmol(igcm_ar)=40.
263          count=count+1
264        endif
265        if (noms(iq).eq."n") then
266          igcm_n=iq
267          mmol(igcm_n)=14.
268          count=count+1
269        endif
270        if (noms(iq).eq."no") then
271          igcm_no=iq
272          mmol(igcm_no)=30.
273          count=count+1
274        endif
275        if (noms(iq).eq."no2") then
276          igcm_no2=iq
277          mmol(igcm_no2)=46.
278          count=count+1
279        endif
280        if (noms(iq).eq."n2d") then
281          igcm_n2d=iq
282          mmol(igcm_n2d)=28.
283          count=count+1
284        endif
285        if (noms(iq).eq."co2plus") then
286          igcm_co2plus=iq
287          mmol(igcm_co2plus)=44.
288          count=count+1
289        endif
290        if (noms(iq).eq."oplus") then
291          igcm_oplus=iq
292          mmol(igcm_oplus)=16.
293          count=count+1
294        endif
295        if (noms(iq).eq."o2plus") then
296          igcm_o2plus=iq
297          mmol(igcm_o2plus)=32.
298          count=count+1
299        endif
300        if (noms(iq).eq."coplus") then
301          igcm_coplus=iq
302          mmol(igcm_coplus)=28.
303          count=count+1
304        endif
305        if (noms(iq).eq."cplus") then
306          igcm_cplus=iq
307          mmol(igcm_cplus)=12.
308          count=count+1
309        endif
310        if (noms(iq).eq."nplus") then
311          igcm_nplus=iq
312          mmol(igcm_nplus)=14.
313          count=count+1
314        endif
315        if (noms(iq).eq."noplus") then
316          igcm_noplus=iq
317          mmol(igcm_noplus)=30.
318          count=count+1
319        endif
320        if (noms(iq).eq."n2plus") then
321          igcm_n2plus=iq
322          mmol(igcm_n2plus)=28.
323          count=count+1
324        endif
325        if (noms(iq).eq."hplus") then
326          igcm_hplus=iq
327          mmol(igcm_hplus)=1.
328          count=count+1
329        endif
330        if (noms(iq).eq."hco2plus") then
331          igcm_hco2plus=iq
332          mmol(igcm_hco2plus)=45.
333          count=count+1
334        endif
335        if (noms(iq).eq."elec") then
336          igcm_elec=iq
337          mmol(igcm_elec)=1./1822.89
338          count=count+1
339        endif
340        if (noms(iq).eq."h2o_vap") then
341          igcm_h2o_vap=iq
342          mmol(igcm_h2o_vap)=18.
343          count=count+1
344        endif
345        if (noms(iq).eq."h2o_ice") then
346          igcm_h2o_ice=iq
347          mmol(igcm_h2o_ice)=18.
348          count=count+1
349        endif
350        ! Other stuff: e.g. for simulations using co2 + neutral gaz
351        if (noms(iq).eq."Ar_N2") then
352          igcm_ar_n2=iq
353          mmol(igcm_ar_n2)=30.
354          count=count+1
355        endif
356
357      enddo ! of do iq=1,nq
358     
359      ! check that we identified all tracers:
360      if (count.ne.nq) then
361        write(*,*) "initracer: found only ",count," tracers"
362        write(*,*) "               expected ",nq
363        do iq=1,count
364          write(*,*)'      ',iq,' ',trim(noms(iq))
365        enddo
366        stop
367      else
368        write(*,*) "initracer: found all expected tracers, namely:"
369        do iq=1,nq
370          write(*,*)'      ',iq,' ',trim(noms(iq))
371        enddo
372      endif
373
374      ! if water cycle but iceparty=.false., there will nevertheless be
375      ! water ice at the surface (iceparty is not used anymore, but this
376      ! part is still relevant, as we want to stay compatible with the
377      ! older versions).
378      if (water.and.(igcm_h2o_ice.eq.0)) then
379        igcm_h2o_ice=igcm_h2o_vap ! so that qsurf(i_h2o_ice) is identified
380                                  ! even though there is no q(i_h2o_ice)
381      else
382       ! surface ice qsurf(i_h2o_ice) was loaded twice by phyetat0,
383       ! as qsurf(i_h2o_vap) & as qsurf(i_h2o_ice), so to be clean:
384       if (igcm_h2o_vap.ne.0) then
385         qsurf(1:ngrid,igcm_h2o_vap)=0
386       endif
387      endif
388
389c------------------------------------------------------------
390c     Initialize tracers .... (in tracer_mod)
391c------------------------------------------------------------
392      ! start by setting everything to (default) zero
393      rho_q(1:nq)=0     ! tracer density (kg.m-3)
394      radius(1:nq)=0.   ! tracer particle radius (m)
395      alpha_lift(1:nq) =0.  ! tracer saltation vertical flux/horiz flux ratio (m-1)
396      alpha_devil(1:nq)=0.  ! tracer lifting coefficient by dust devils
397
398
399      ! some reference values
400      rho_dust=2500.  ! Mars dust density (kg.m-3)
401      rho_ice=920.    ! Water ice density (kg.m-3)
402      nuice_ref=0.1   ! Effective variance nueff of the
403                      ! water-ice size distribution
404      !!!nuice_sed=0.45   ! Sedimentation effective variance
405                      ! of the water-ice size distribution
406
407      if (doubleq) then
408c       "doubleq" technique
409c       -------------------
410c      (transport of mass and number mixing ratio)
411c       iq=1: Q mass mixing ratio, iq=2: N number mixing ratio
412
413        if( (nq.lt.2).or.(water.and.(nq.lt.4)) ) then
414          write(*,*)'initracer: nq is too low : nq=', nq
415          write(*,*)'water= ',water,' doubleq= ',doubleq   
416        end if
417
418        nueff_lift = 0.5
419        varian=sqrt(log(1.+nueff_lift))
420
421        rho_q(igcm_dust_mass)=rho_dust
422        rho_q(igcm_dust_number)=rho_dust
423
424c       Intermediate calcul for computing geometric mean radius r0
425c       as a function of mass and number mixing ratio Q and N
426c       (r0 = (r3n_q * Q/ N)^(1/3))
427        r3n_q = exp(-4.5*varian**2)*(3./4.)/(pi*rho_dust)
428
429c       Intermediate calcul for computing effective radius reff
430c       from geometric mean radius r0
431c       (reff = ref_r0 * r0)
432        ref_r0 = exp(2.5*varian**2)
433       
434c       lifted dust :
435c       '''''''''''
436        reff_lift = 3.0e-6 !3.e-6 !Effective radius of lifted dust (m)
437        alpha_devil(igcm_dust_mass)=9.e-9   !  dust devil lift mass coeff
438c       alpha_lift(igcm_dust_mass)=3.0e-15  !  Lifted mass coeff
439        alpha_lift(igcm_dust_mass)=1.e-6 !1.e-6 !Lifted mass coeff
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 (scavenging) then
600       ! verify that we indeed have ccn_mass and ccn_number tracers
601         if (igcm_ccn_mass.eq.0) then
602           write(*,*) "initracer: error !!"
603           write(*,*) "  cannot use scavenging option without ",
604     &                "a ccn_mass tracer !"
605           stop
606         endif
607         if (igcm_ccn_number.eq.0) then
608           write(*,*) "initracer: error !!"
609           write(*,*) "  cannot use scavenging option without ",
610     &                "a ccn_number tracer !"
611           stop
612         endif
613       endif ! of if (scavenging)
614
615       if (photochem .or. callthermos) then
616       ! verify that we indeed have the chemistry tracers
617         if (igcm_co2.eq.0) then
618           write(*,*) "initracer: error !!"
619           write(*,*) "  cannot use chemistry option without ",
620     &                "a co2 tracer !"
621         stop
622         endif
623         if (igcm_co.eq.0) then
624           write(*,*) "initracer: error !!"
625           write(*,*) "  cannot use chemistry option without ",
626     &                "a co tracer !"
627         stop
628         endif
629         if (igcm_o.eq.0) then
630           write(*,*) "initracer: error !!"
631           write(*,*) "  cannot use chemistry option without ",
632     &                "a o tracer !"
633         stop
634         endif
635         if (igcm_o1d.eq.0) then
636           write(*,*) "initracer: error !!"
637           write(*,*) "  cannot use chemistry option without ",
638     &                "a o1d tracer !"
639         stop
640         endif
641         if (igcm_o2.eq.0) then
642           write(*,*) "initracer: error !!"
643           write(*,*) "  cannot use chemistry option without ",
644     &                "an o2 tracer !"
645         stop
646         endif
647         if (igcm_o3.eq.0) then
648           write(*,*) "initracer: error !!"
649           write(*,*) "  cannot use chemistry option without ",
650     &                "an o3 tracer !"
651         stop
652         endif
653         if (igcm_h.eq.0) then
654           write(*,*) "initracer: error !!"
655           write(*,*) "  cannot use chemistry option without ",
656     &                "a h tracer !"
657         stop
658         endif
659         if (igcm_h2.eq.0) then
660           write(*,*) "initracer: error !!"
661           write(*,*) "  cannot use chemistry option without ",
662     &                "a h2 tracer !"
663         stop
664         endif
665         if (igcm_oh.eq.0) then
666           write(*,*) "initracer: error !!"
667           write(*,*) "  cannot use chemistry option without ",
668     &                "an oh tracer !"
669         stop
670         endif
671         if (igcm_ho2.eq.0) then
672           write(*,*) "initracer: error !!"
673           write(*,*) "  cannot use chemistry option without ",
674     &                "a ho2 tracer !"
675         stop
676         endif
677         if (igcm_h2o2.eq.0) then
678           write(*,*) "initracer: error !!"
679           write(*,*) "  cannot use chemistry option without ",
680     &                "a h2o2 tracer !"
681         stop
682         endif
683         if (igcm_n2.eq.0) then
684           write(*,*) "initracer: error !!"
685           write(*,*) "  cannot use chemistry option without ",
686     &                "a n2 tracer !"
687         stop
688         endif
689         if (igcm_ar.eq.0) then
690           write(*,*) "initracer: error !!"
691           write(*,*) "  cannot use chemistry option without ",
692     &                "an ar tracer !"
693         stop
694         endif
695       endif ! of if (photochem .or. callthermos)
696
697      end
Note: See TracBrowser for help on using the repository browser.