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

Last change on this file since 2394 was 2324, checked in by mvals, 5 years ago

Mars GCM:
Follow-up of the last commit for the transport of the isotopic ratio: cleaning to help the user:
-initracer.F: hdo must be defined as an isotope (meaning its "father" has to be precised in traceur.def) and must be placed at the end of the list of
tracers in traceur.def.
-/deftank/traceur.def.isotopes: writing of traceur.def in the case of hdo=true has been simplified to match both the 3D and the 1D simulations.
-simpleclouds.F,hdo_surfex_mod.F,physiq_mod.F: thresholds of 1.e-16 have been replaced by the variable qperemin defined in tracer_mod.F.
MV

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