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

Last change on this file since 2325 was 2322, checked in by mvals, 5 years ago

Mars GCM:
Extent of the transport of the isotopic ratio implemented in the dynamics to all the Van Leer transport schemes used in the physics (for now it only
concerns the tracer HDO).

  • libf/dynphy_lonlat/phymars/: iniphysiq_mod.F90: transmission of the content of variables describing the isotopes defined in the dynamics (precisely by dyn3d_common/infotrac.F90,

which reads traceur.def) to the physics

  • libf/phymars/: phys_state_var_init_mod.F90, tracer_mod.F : initialisation of the variables describing the isotopes in the physics callsedim_mod.F: implementation of the transport of the isotopic ratio in the Van Leer scheme used for sedimentation (applies to hdo ice) co2condens_mod.F: implementation of the transport of the isotopic ratio in the Van Leer scheme used for condensation of CO2 (applies to hdo ice and

vapour)
MV

File size: 7.6 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
51
[1036]52      ! water
53      integer,save :: igcm_h2o_vap ! water vapour
54      integer,save :: igcm_h2o_ice ! water ice
[2312]55      integer,save :: igcm_hdo_vap ! hdo vapour
56      integer,save :: igcm_hdo_ice ! hdo ice
[1617]57      integer,save :: igcm_co2_ice ! co2 ice
58
[1036]59      ! chemistry:
60      integer,save :: igcm_co2
61      integer,save :: igcm_co
62      integer,save :: igcm_o
63      integer,save :: igcm_o1d
64      integer,save :: igcm_o2
65      integer,save :: igcm_o3
66      integer,save :: igcm_h
67      integer,save :: igcm_h2
68      integer,save :: igcm_oh
69      integer,save :: igcm_ho2
70      integer,save :: igcm_h2o2
71      integer,save :: igcm_n2
72      integer,save :: igcm_ar
73      integer,save :: igcm_n
74      integer,save :: igcm_no
75      integer,save :: igcm_no2
76      integer,save :: igcm_n2d
[1660]77      integer,save :: igcm_he
[1036]78      integer,save :: igcm_ch4
79      ! Ions
80      integer,save :: igcm_co2plus
81      integer,save :: igcm_oplus
82      integer,save :: igcm_o2plus
83      integer,save :: igcm_coplus
84      integer,save :: igcm_cplus
85      integer,save :: igcm_nplus
86      integer,save :: igcm_noplus
87      integer,save :: igcm_n2plus
88      integer,save :: igcm_hplus
89      integer,save :: igcm_hco2plus
[2284]90      integer,save :: igcm_hcoplus
[2302]91      integer,save :: igcm_h2oplus
[2321]92      integer,save :: igcm_h3oplus
93      integer,save :: igcm_ohplus
[1036]94      integer,save :: igcm_elec
95      ! other tracers
96      integer,save :: igcm_ar_n2 ! for simulations using co2 +neutral gas
[2322]97      ! MVals: isotopes
98      integer, save                 :: nqperes ! numbers of tracers defined as "peres"
99      integer, allocatable, save    :: nqfils(:) ! numbers of sons ("fils") of the considered tracer
100      integer, allocatable, save    :: iqfils(:,:) ! indice of a son, ex: iqfils(nqfils(ipere),ipere)
101      real, parameter               :: qperemin=1.e-16 ! threschold for the "pere" mixing ratio qpere to calculate Ratio=qfils/qpere
102      real, parameter               :: masseqmin=1.e-16 ! threschold for the "pere" transporting masse
103      !integer, allocatable, save    :: nqdesc(:) ! number of sons + all gran-sons over all generations: not useful for now in the martian case as there are no gran-sons
[1036]104
105!-----------------------------------------------------------------------
106
[1621]107  contains
108 
[2322]109    subroutine ini_tracer_mod(nq,tname,dyn_nqdesc,dyn_iqfils,dyn_nqperes,dyn_nqfils)! MVals: variables isotopes
[1621]110      implicit none
111     
112      integer,intent(in) :: nq ! number of tracers
113      character(len=*),intent(in) :: tname(nq) ! tracer names
[2322]114      !MVals: variables isotopes
115      integer,intent(in) :: dyn_nqperes
116      integer,intent(in) :: dyn_nqfils(nq)
117      integer,intent(in) :: dyn_nqdesc(nq)
118      integer,intent(in) :: dyn_iqfils(nq,nq)
[1621]119     
120      integer :: iq, count
121      character(len=20) :: txt ! to store some text
122     
123      ! set dimension and tracer names
124      nqmx=nq
125      allocate(noms(nq))
126      do iq=1,nq
127        noms(iq)=tname(iq)
128        write(*,*) "tracer_mod names : ", trim(noms(iq))
129      enddo
[2322]130
131      !MVals: isotopes variables initialisation
132      do iq=1,nq
133        if (dyn_nqfils(iq).ne.dyn_nqdesc(iq)) then
134          write(*,*) ' for now all descendants must be sons: check the', &
135                     '  relations between tracers in traceur.def !'
136          call abort_physic("ini_tracer_mod","relatives pattern between tracers not accepted",1)
137        endif
138      enddo
139      allocate(nqfils(nq))!,nqdesc(nq))   
140      allocate(iqfils(nq,nq))
141      nqperes=dyn_nqperes   
142      nqfils(:)=dyn_nqfils(:)
143      iqfils(:,:)=dyn_iqfils(:,:)
[1633]144     
145#ifndef MESOSCALE
[1621]146      ! check if tracers have 'old' names
147      count=0
148      do iq=1,nq
149        txt=" "
150        write(txt,'(a1,i2.2)') 'q',iq
151        if (txt.eq.tname(iq)) then
152          count=count+1
153        endif
154      enddo ! of do iq=1,nq
155     
[1941]156      if ((count.eq.nq).and.(nq.ne.0)) then
[1621]157        write(*,*) "ini_tracer_mod: tracers seem to follow old naming ", &
158                   "convention (q01,q02,...)"
159        write(*,*) "you should run newstart to rename them"
[1941]160        call abort_physic("ini_tracer_mod","tracer name issue",1)
[1621]161      endif
162#endif
163           
164      ! allocate module arrays:
[1770]165      ! -- not domain-dependent
[1621]166      allocate(mmol(nq))
167      allocate(radius(nq))
168      allocate(rho_q(nq))
169      allocate(alpha_lift(nq))
170      allocate(alpha_devil(nq))
171      allocate(igcm_dustbin(nq))
172      allocate(nqdust(nq))
173     
174    end subroutine ini_tracer_mod
175
[1770]176    subroutine end_tracer_mod
177
178    implicit none
179
180      if (allocated(noms)) deallocate(noms)
181      if (allocated(mmol)) deallocate(mmol)
182      if (allocated(radius)) deallocate(radius)
183      if (allocated(rho_q)) deallocate(rho_q)
184      if (allocated(alpha_lift)) deallocate(alpha_lift)
185      if (allocated(alpha_devil)) deallocate(alpha_devil)
186      if (allocated(igcm_dustbin)) deallocate(igcm_dustbin)
187      if (allocated(nqdust)) deallocate(nqdust)
188
189    end subroutine end_tracer_mod
190
[1036]191end module tracer_mod
Note: See TracBrowser for help on using the repository browser.