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

Last change on this file since 2417 was 2409, checked in by emillour, 5 years ago

Mars GCM:
Code tidying : make a "dust_param_mod" module to store dust cycle relevant flags
and variables (and remove them from callkeys.h)
EM

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