source: trunk/LMDZ.VENUS/libf/phyvenus/concentrations2.F @ 3892

Last change on this file since 3892 was 3884, checked in by ikovalenko, 4 months ago
File size: 8.0 KB
Line 
1      SUBROUTINE concentrations2(pplay,t_seri,tr_seri, nqmx)
2
3      use dimphy
4      use conc,  only: mmean, rho, Akknew, rnew, cpnew
5      use cpdet_phy_mod, only: cpdet                       
6      USE chemparam_mod
7      USE infotrac_phy, ONLY: tname
8      USE clesphys_mod
9      USE YOMCST_mod
10      implicit none
11
12!=======================================================================
13! CALCULATION OF MEAN MOLECULAR MASS, Cp, Akk and R
14!
15! mmean(klon,klev)      amu
16! cpnew(klon,klev)      J/kg/K
17! rnew(klon,klev)       J/kg/K
18! akknew(klon,klev)     coefficient of thermal conduction
19!
20! version: April 2012 - Franck Lefevre
21!=======================================================================
22
23!     declarations
24 
25c#include "YOMCST.h"
26c#include "clesphys.h"
27c#include "comdiurn.h"
28c#include "chimiedata.h"
29c#include "tracer.h"
30c#include "mmol.h"
31
32!     input/output
33
34      real pplay(klon,klev)
35      integer,intent(in) :: nqmx    ! number of tracers
36      real t_seri(klon, klev)
37      real tr_seri(klon,klev,nqmx)
38
39!     local variables
40
41      integer       :: i, l, ig, iq
42      integer, save :: nbq
43      integer,allocatable,save :: niq(:)
44      real          :: ni(nqmx), ntot
45      real          :: zt(klon, klev)
46      real          :: zq(klon, klev, nqmx)
47      real,allocatable,save    :: aki(:)
48      real,allocatable,save    :: cpi(:)
49      real, save    :: akin,akin2
50
51      logical, save :: firstcall = .true.
52
53      if (firstcall) then
54
55!        initialize thermal conductivity and specific heat coefficients
56!        values are taken from the literature [J/kg K]
57
58         ! allocate local saved arrays:
59         allocate(aki(nqmx))
60         allocate(cpi(nqmx))
61         allocate(niq(nqmx))
62
63!        find index of chemical tracers to use
64!        initialize thermal conductivity and specific heat coefficients
65!        !? values are estimated
66
67         nbq = 0 ! to count number of tracers used in this subroutine
68
69!        aki values comes from Aeronomy part B by P.M. BANKS / G. KOCKARTS – page 12-20-24)
70
71!        Ions are not here because the sum of all ions abundace is not
72!        above 10^-4 until 250 km and we don't have their cpi and aki.
73
74!        Heat capacity for H, He, N, N2, O, O2, CO2, CO:
75!        Circular of the bureau of Standards no. 564: tables of thermal properties of gases comprising [...]
76!        Tables of Thermodynamic and Transport Properties of Air, Argon, Carbon Dioxide, Carbon Monoxide,
77!        Hydrogen (molecular and atomic), Nitrogen (molecular and atomic), Oxygen (molecular and atomic), and Steam
78!        https://www.govinfo.gov/content/pkg/GOVPUB-C13-89baf9f9b4a43e5f25820bd51b0f3f11/pdf/GOVPUB-C13-89baf9f9b4a43e5f25820bd51b0f3f11.pdf
79       
80
81         if (i_co2 /= 0) then
82            nbq = nbq + 1
83            niq(nbq) = i_co2
84            aki(nbq) = 3.072e-4
85            cpi(nbq) = 0.834e3
86         end if
87         if (i_co /= 0) then
88            nbq = nbq + 1
89            niq(nbq) = i_co
90            aki(nbq) = 4.87e-4
91            cpi(nbq) = 1.034e3
92         end if
93         if (i_o /= 0) then
94            nbq = nbq + 1
95            niq(nbq) = i_o
96            aki(nbq) = 7.59e-4
97            cpi(nbq) = 1.3e3
98         end if
99         if (i_o1d /= 0) then
100            nbq = nbq + 1
101            niq(nbq) = i_o1d
102            aki(nbq) = 7.59e-4  !?
103            cpi(nbq) = 1.3e3    !?
104         end if
105         if (i_o2 /= 0) then
106            nbq = nbq + 1
107            niq(nbq) = i_o2
108            aki(nbq) = 5.68e-4
109            cpi(nbq) = 0.9194e3
110         end if
111         if (i_o3 /= 0) then
112            nbq = nbq + 1
113            niq(nbq) = i_o3
114            aki(nbq) = 3.00e-4  !?
115            cpi(nbq) = 0.800e3  !?
116         end if
117         if (i_h /= 0) then
118            nbq = nbq + 1
119            niq(nbq) = i_h
120            !aki(nbq) = 0.0      !! valeur d'origine
121            aki(nbq) = 37.9e-4   !??? A verifier
122            cpi(nbq) = 20.780e3
123         end if
124         if (i_h2 /= 0) then
125            nbq = nbq + 1
126            niq(nbq) = i_h2
127            aki(nbq) = 36.314e-4
128            cpi(nbq) = 14.266e3
129         end if
130         if (i_oh /= 0) then
131            nbq = nbq + 1
132            niq(nbq) = i_oh
133            aki(nbq)  = 7.00e-4 !?
134            cpi(nbq)  = 1.045e3
135         end if
136         if (i_ho2 /= 0) then
137            nbq = nbq + 1
138            niq(nbq) = i_ho2
139            aki(nbq) = 0.0
140            cpi(nbq) = 1.065e3  !?
141         end if
142         if (i_n2 /= 0) then
143            nbq = nbq + 1
144            niq(nbq) = i_n2
145            aki(nbq) = 5.6e-4
146            cpi(nbq) = 1.034e3
147         end if
148c         if (i_ar /= 0) then
149c            nbq = nbq + 1
150c            niq(nbq) = i_ar
151c            aki(nbq) = 0.0      !?
152c            cpi(nbq) = 1.000e3  !?
153c         end if
154         if (i_h2o /= 0) then
155            nbq = nbq + 1
156            niq(nbq) = i_h2o
157            aki(nbq) = 0.0
158            cpi(nbq) = 1.870e3
159         end if
160         if (i_n /= 0) then
161            nbq = nbq + 1
162            niq(nbq) = i_n
163            aki(nbq) = 0.0
164            cpi(nbq) = 1.4844e3
165         endif
166         if(i_no /= 0) then
167            nbq = nbq + 1
168            niq(nbq) = i_no
169            aki(nbq) = 0.0
170            cpi(nbq) = 0.0
171         endif
172         if(i_no2 /= 0) then
173            nbq = nbq + 1
174            niq(nbq) = i_no2
175            aki(nbq) = 0.0
176            cpi(nbq) = 0.0
177         endif
178         if(i_n2d /= 0) then
179            nbq = nbq + 1
180            niq(nbq) = i_n2d
181            aki(nbq) = 0.0
182            cpi(nbq) = 1.4844e3 !?
183         endif
184         if (i_he /= 0) then
185            nbq = nbq + 1
186            niq(nbq) = i_he
187            aki(nbq) = 29.9e-4
188            cpi(nbq) = 5.2e3
189         end if
190
191         ! tell the world about it:
192         write(*,*) "concentrations: firstcall, nbq=",nbq
193!         write(*,*) "test M_tr(nbq)=",M_tr(nbq)
194!         write(*,*) "  niq(1:nbq)=",niq(1:nbq)
195!         write(*,*) "  aki(1:nbq)=",aki(1:nbq)
196!         write(*,*) "  cpi(1:nbq)=",cpi(1:nbq)
197         do i = 1,nbq
198            write(*,*) "tname(i)=",tname(i)
199            write(*,*) "tname(niq(i))=",tname(niq(i))
200         end do
201         firstcall = .false.
202      end if ! if (firstcall)
203
204!     update temperature
205
206      do l = 1,klev
207         do ig = 1,klon
208            zt(ig,l) = t_seri(ig,l)
209         end do
210      end do
211
212
213!     update mass mixing ratio tracers
214
215      do l = 1,klev
216         do ig = 1,klon
217            do i = 1,nqmx
218!               iq = niq(i)
219               zq(ig,l,i) = max(1.e-30, tr_seri(ig,l,i))
220            end do
221         end do
222      end do
223
224!     mmean : mean molecular mass
225!     rho   : mass density [kg/m3]
226!     rnew  : specific gas constant
227   
228      mmean(:,:)  = 0.
229      rho(:,:) = 0.     
230
231      do l = 1,klev
232         do ig = 1,klon
233            do i = 1,nqmx-nmicro
234c               iq = niq(i)
235               mmean(ig,l) = mmean(ig,l) + zq(ig,l,i)/M_tr(i)
236            end do
237            mmean(ig,l) = 1./mmean(ig,l)
238            rnew(ig,l) = 8.314/mmean(ig,l)*1.e3     ! J/kg K
239c            write(*,*),'Mmean in concentration2: ',ig, l, mmean(ig,l)
240         end do
241      end do
242
243!     cpnew  : specific heat
244!     akknew : thermal conductivity cofficient
245     
246      cpnew(:,:)  = 0.
247      akknew(:,:) = 0.
248
249      do l = 1,klev
250          do ig = 1,klon
251
252            ntot = pplay(ig,l)/(RKBOL*zt(ig,l))*1.e-6  ! in #/cm3
253            rho(ig,l) = (ntot * mmean(ig,l))/RNAVO*1.e3     ! in kg/m3
254
255c            write(*,*),'Air density: ',ig, l, rho(0,l)           
256
257!!  WARNING -> Cp here below doesn't depend on T (cpdet)
258
259            do i = 1,nbq
260               iq = niq(i)
261               ni(i) = ntot*zq(ig,l,iq)*mmean(ig,l)/M_tr(iq)
262!! On a une super formule pour calculer cp_co2 sur Venus
263               if (iq == i_co2) then
264                  cpnew(ig,l) = cpnew(ig,l) + ni(i)*cpdet(zt(ig,l))
265               else
266                  cpnew(ig,l) = cpnew(ig,l) + ni(i)*cpi(i)
267               end if
268               akknew(ig,l) = akknew(ig,l) + ni(i)*aki(i)
269            end do
270 
271            cpnew(ig,l) = cpnew(ig,l)/ntot
272            akknew(ig,l)= akknew(ig,l)/ntot
273
274
275          end do
276       end do
277
278      return
279      end
Note: See TracBrowser for help on using the repository browser.