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

Last change on this file since 2156 was 1974, checked in by mvals, 6 years ago

Mars GCM:
Integration of the detached dust layer parametrizations (rocket dust storm, slope wind lifting, CW, and dust injection scheme, DB).
Still experimental, default behaviour (rdstorm=.false., dustinjection=0) identical to previous revision.
NB: Updated newstart requires an updated "surface.nc" containing the "hmons" field.
EM+MV

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