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

Last change on this file since 2740 was 2659, checked in by cmathe, 3 years ago

ticket 100 resolved

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