source: trunk/LMDZ.MARS/libf/phymars/tracer_mod.F90 @ 2566

Last change on this file since 2566 was 2562, checked in by cmathe, 4 years ago

GCM MARS: CO2 clouds microphysics improvements

File size: 7.4 KB
RevLine 
[1036]1module tracer_mod
2
3 implicit none
4 
5      ! number of tracers:
[1224]6      integer,save :: nqmx ! initialized in conf_phys
[1617]7   
[1974]8      character*30,allocatable,save ::  noms(:)  ! name of the tracer
[1036]9      real,allocatable,save :: mmol(:)           ! mole mass of tracer (g/mol-1)
10      real,allocatable,save :: radius(:)   ! dust and ice particle radius (m)
11      real,allocatable,save :: rho_q(:)    ! tracer densities (kg.m-3)
12      real,allocatable,save :: alpha_lift(:) ! saltation vertical flux/horiz flux ratio (m-1)
13      real,allocatable,save :: alpha_devil(:) ! lifting coeeficient by dust devil
14
15      real,save :: varian      ! Characteristic variance of log-normal distribution
16      real,save :: r3n_q     ! used to compute r0 from number and mass mixing ratio
17      real,save :: rho_dust     ! Mars dust density (kg.m-3)
18      real,save :: rho_ice     ! Water ice density (kg.m-3)
19      real,save :: nuice_ref   ! Effective variance of the water ice dist.
20      real,save :: nuice_sed   ! Sedimentation effective variance of the water ice dist.
21      real,save :: ref_r0        ! for computing reff=ref_r0*r0 (in log.n. distribution)
[1617]22      real,save :: rho_ice_co2     ! co2 ice density (kg.m-3)
23      real,save :: nuiceco2_sed   ! Sedimentation effective variance of the co2 ice dist.
24      real,save :: nuiceco2_ref   ! Effective variance of the co2 ice dist.
[1974]25     
[1036]26      real,save :: ccn_factor  ! ratio of nuclei for water ice particles
27
[1224]28      INTEGER,ALLOCATABLE,SAVE :: nqdust(:) ! to store the indexes of dust tracers (cf aeropacity)
[1617]29      real,allocatable,save :: dryness(:)!"Dryness coefficient" for grnd water ice sublimation
[1224]30
[1617]31
[1036]32! tracer indexes: these are initialized in initracer and should be 0 if the
33!                 corresponding tracer does not exist
34      ! dust
35      integer,allocatable,save :: igcm_dustbin(:) ! for dustbin 'dust' tracers
36      ! dust, special doubleq case
37      integer,save :: igcm_dust_mass   ! dust mass mixing ratio
38                                  !   (for transported dust)
39      integer,save :: igcm_dust_number ! dust number mixing ratio
40                                  !   (transported dust)
41      integer,save :: igcm_ccn_mass   ! CCN mass mixing ratio
42      integer,save :: igcm_ccn_number ! CCN number mixing ratio
43      integer,save :: igcm_dust_submicron ! submicron dust mixing ratio
[1974]44      integer,save :: igcm_stormdust_mass   !  storm dust mass mixing ratio
45      integer,save :: igcm_stormdust_number !  storm dust number mixing ratio
[2199]46      integer,save :: igcm_topdust_mass   !  topdust mass mixing ratio
47      integer,save :: igcm_topdust_number !  topdust number mixing ratio
48
[1617]49      integer,save :: igcm_ccnco2_mass   ! CCN (dust and/or water ice) for CO2 mass mixing ratio
50      integer,save :: igcm_ccnco2_number ! CCN (dust and/or water ice) for CO2 number mixing ratio
[2562]51      integer,save :: igcm_ccnco2_h2o_mass_ice   ! CCN (dust and/or water ice) for CO2 mass mixing ratio
52      integer,save :: igcm_ccnco2_h2o_mass_ccn   ! CCN (dust and/or water ice) for CO2 mass mixing ratio
53      integer,save :: igcm_ccnco2_h2o_number ! CCN (dust and/or water ice) for CO2 number mixing ratio
[1617]54
[1036]55      ! water
56      integer,save :: igcm_h2o_vap ! water vapour
57      integer,save :: igcm_h2o_ice ! water ice
[2312]58      integer,save :: igcm_hdo_vap ! hdo vapour
59      integer,save :: igcm_hdo_ice ! hdo ice
[1617]60      integer,save :: igcm_co2_ice ! co2 ice
61
[1036]62      ! chemistry:
63      integer,save :: igcm_co2
64      integer,save :: igcm_co
65      integer,save :: igcm_o
66      integer,save :: igcm_o1d
67      integer,save :: igcm_o2
68      integer,save :: igcm_o3
69      integer,save :: igcm_h
70      integer,save :: igcm_h2
71      integer,save :: igcm_oh
72      integer,save :: igcm_ho2
73      integer,save :: igcm_h2o2
74      integer,save :: igcm_n2
75      integer,save :: igcm_ar
76      integer,save :: igcm_n
77      integer,save :: igcm_no
78      integer,save :: igcm_no2
79      integer,save :: igcm_n2d
[1660]80      integer,save :: igcm_he
[1036]81      integer,save :: igcm_ch4
[2461]82      !Deuterated species derived from HDO
83      integer,save :: igcm_od
84      integer,save :: igcm_d
85      integer,save :: igcm_hd
86      integer,save :: igcm_do2
87      integer,save :: igcm_hdo2
[1036]88      ! Ions
89      integer,save :: igcm_co2plus
90      integer,save :: igcm_oplus
91      integer,save :: igcm_o2plus
92      integer,save :: igcm_coplus
93      integer,save :: igcm_cplus
94      integer,save :: igcm_nplus
95      integer,save :: igcm_noplus
96      integer,save :: igcm_n2plus
97      integer,save :: igcm_hplus
98      integer,save :: igcm_hco2plus
[2284]99      integer,save :: igcm_hcoplus
[2302]100      integer,save :: igcm_h2oplus
[2321]101      integer,save :: igcm_h3oplus
102      integer,save :: igcm_ohplus
[1036]103      integer,save :: igcm_elec
104      ! other tracers
105      integer,save :: igcm_ar_n2 ! for simulations using co2 +neutral gas
[2322]106      ! MVals: isotopes
107      integer, save                 :: nqperes ! numbers of tracers defined as "peres"
108      integer, allocatable, save    :: nqfils(:) ! numbers of sons ("fils") of the considered tracer
109      real, parameter               :: qperemin=1.e-16 ! threschold for the "pere" mixing ratio qpere to calculate Ratio=qfils/qpere
[2332]110      real, parameter               :: masseqmin=1.e-16 ! threschold for the "pere" transporting masse martian case as there are no gran-sons
[1036]111
112!-----------------------------------------------------------------------
113
[1621]114  contains
115 
[2332]116    subroutine ini_tracer_mod(nq,tname,dyn_nqperes,dyn_nqfils)! MVals: variables isotopes
[1621]117      implicit none
118     
119      integer,intent(in) :: nq ! number of tracers
120      character(len=*),intent(in) :: tname(nq) ! tracer names
[2322]121      !MVals: variables isotopes
122      integer,intent(in) :: dyn_nqperes
123      integer,intent(in) :: dyn_nqfils(nq)
[1621]124     
125      integer :: iq, count
126      character(len=20) :: txt ! to store some text
127     
128      ! set dimension and tracer names
129      nqmx=nq
130      allocate(noms(nq))
131      do iq=1,nq
132        noms(iq)=tname(iq)
133        write(*,*) "tracer_mod names : ", trim(noms(iq))
134      enddo
[2322]135
136      !MVals: isotopes variables initialisation
[2332]137      allocate(nqfils(nq))
[2322]138      nqperes=dyn_nqperes   
139      nqfils(:)=dyn_nqfils(:)
[1633]140     
141#ifndef MESOSCALE
[1621]142      ! check if tracers have 'old' names
143      count=0
144      do iq=1,nq
145        txt=" "
146        write(txt,'(a1,i2.2)') 'q',iq
147        if (txt.eq.tname(iq)) then
148          count=count+1
149        endif
150      enddo ! of do iq=1,nq
151     
[1941]152      if ((count.eq.nq).and.(nq.ne.0)) then
[1621]153        write(*,*) "ini_tracer_mod: tracers seem to follow old naming ", &
154                   "convention (q01,q02,...)"
155        write(*,*) "you should run newstart to rename them"
[1941]156        call abort_physic("ini_tracer_mod","tracer name issue",1)
[1621]157      endif
158#endif
159           
160      ! allocate module arrays:
[1770]161      ! -- not domain-dependent
[1621]162      allocate(mmol(nq))
163      allocate(radius(nq))
164      allocate(rho_q(nq))
165      allocate(alpha_lift(nq))
166      allocate(alpha_devil(nq))
167      allocate(igcm_dustbin(nq))
168      allocate(nqdust(nq))
169     
170    end subroutine ini_tracer_mod
171
[1770]172    subroutine end_tracer_mod
173
174    implicit none
175
176      if (allocated(noms)) deallocate(noms)
177      if (allocated(mmol)) deallocate(mmol)
178      if (allocated(radius)) deallocate(radius)
179      if (allocated(rho_q)) deallocate(rho_q)
180      if (allocated(alpha_lift)) deallocate(alpha_lift)
181      if (allocated(alpha_devil)) deallocate(alpha_devil)
182      if (allocated(igcm_dustbin)) deallocate(igcm_dustbin)
183      if (allocated(nqdust)) deallocate(nqdust)
184
185    end subroutine end_tracer_mod
186
[1036]187end module tracer_mod
Note: See TracBrowser for help on using the repository browser.