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

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

Further work on full dynamics/physics separation.

LMDZ.COMMON:

  • added phy_common/vertical_layers_mod.F90 to store information on vertical grid. This is where routines in the physics should get the information.
  • The contents of vertical_layers_mod intialized via dynphy_lonlat/inigeomphy_mod.F90.

LMDZ.MARS:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • created an "ini_tracer_mod" routine in module "tracer_mod" for a cleaner initialization of the later.
  • removed some purely dynamics-related outputs (etot0, zoom parameters, etc.) from diagfi.nc and stats.nc outputs as these informations are not available in the physics.

LMDZ.GENERIC:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • added nqtot to tracer_h.F90.
  • removed some purely dynamics-related outputs (etot0, zoom parameters, etc.) from diagfi.nc and stats.nc outputs as these informations are not available in the physics.

LMDZ.VENUS:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • added infotrac_phy.F90 to store information on tracers in the physics. Initialized via iniphysiq.
  • added cpdet_phy_mod.F90 to store t2tpot etc. functions to be used in the physics. Initialized via iniphysiq. IMPORTANT: there are some hard-coded constants! These should match what is in cpdet_mod.F90 in the dynamics.
  • got rid of references to moyzon_mod module within the physics. The required variables (tmoy, plevmoy) are passed to the physics as arguments to physiq.

LMDZ.TITAN:

  • added infotrac_phy.F90 to store information on tracers in the physics. Initialized via iniphysiq.
  • added cpdet_phy_mod.F90 to store t2tpot etc. functions to be used in the physics.
  • Extra work required to completely decouple physics and dynamics: moyzon_mod should be cleaned up and information passed from dynamics to physics as as arguments. Likewise moyzon_ch and moyzon_mu should not be queried from logic_mod (which is in the dynamics).

EM

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