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

Last change on this file since 3461 was 3005, checked in by amartinez, 16 months ago

Venus PCM correction

Dans concentrations2.F, l'helium était compté deux fois dans le calcul de la capacité calorifique et conductivité.

Pas d'effets pour les pressions P > 1E-5 Pa, faible pour P < 1E-5 Pa.

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