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

Last change on this file since 2732 was 2686, checked in by slebonnois, 3 years ago

SL+AM : various corrections prior to VCD 2.0

File size: 7.2 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         if (i_co2 /= 0) then
68            nbq = nbq + 1
69            niq(nbq) = i_co2
70            aki(nbq) = 3.072e-4
71            cpi(nbq) = 0.834e3
72         end if
73         if (i_co /= 0) then
74            nbq = nbq + 1
75            niq(nbq) = i_co
76            aki(nbq) = 4.87e-4
77            cpi(nbq) = 1.034e3
78         end if
79         if (i_o /= 0) then
80            nbq = nbq + 1
81            niq(nbq) = i_o
82            aki(nbq) = 7.59e-4
83            cpi(nbq) = 1.3e3
84         end if
85         if (i_o1d /= 0) then
86            nbq = nbq + 1
87            niq(nbq) = i_o1d
88            aki(nbq) = 7.59e-4  !?
89            cpi(nbq) = 1.3e3    !?
90         end if
91         if (i_o2 /= 0) then
92            nbq = nbq + 1
93            niq(nbq) = i_o2
94            aki(nbq) = 5.68e-4
95            cpi(nbq) = 0.9194e3
96         end if
97         if (i_o3 /= 0) then
98            nbq = nbq + 1
99            niq(nbq) = i_o3
100            aki(nbq) = 3.00e-4  !?
101            cpi(nbq) = 0.800e3  !?
102         end if
103         if (i_h /= 0) then
104            nbq = nbq + 1
105            niq(nbq) = i_h
106            !aki(nbq) = 0.0      !! valeur d'origine
107            aki(nbq) = 37.9e-4   !??? A verifier
108            cpi(nbq) = 20.780e3
109         end if
110         if (i_h2 /= 0) then
111            nbq = nbq + 1
112            niq(nbq) = i_h2
113            aki(nbq) = 36.314e-4
114            cpi(nbq) = 14.266e3
115         end if
116         if (i_oh /= 0) then
117            nbq = nbq + 1
118            niq(nbq) = i_oh
119            aki(nbq)  = 7.00e-4 !?
120            cpi(nbq)  = 1.045e3
121         end if
122         if (i_ho2 /= 0) then
123            nbq = nbq + 1
124            niq(nbq) = i_ho2
125            aki(nbq) = 0.0
126            cpi(nbq) = 1.065e3  !?
127         end if
128         if (i_n2 /= 0) then
129            nbq = nbq + 1
130            niq(nbq) = i_n2
131            aki(nbq) = 5.6e-4
132            cpi(nbq) = 1.034e3
133         end if
134c         if (i_ar /= 0) then
135c            nbq = nbq + 1
136c            niq(nbq) = i_ar
137c            aki(nbq) = 0.0      !?
138c            cpi(nbq) = 1.000e3  !?
139c         end if
140         if (i_h2o /= 0) then
141            nbq = nbq + 1
142            niq(nbq) = i_h2o
143            aki(nbq) = 0.0
144            cpi(nbq) = 1.870e3
145         end if
146c         if (i_n /= 0) then
147c            nbq = nbq + 1
148c            niq(nbq) = i_n
149c            aki(nbq) = 0.0
150c            cpi(nbq) = 0.0
151c         endif
152c         if(i_no /= 0) then
153c            nbq = nbq + 1
154c            niq(nbq) = i_no
155c            aki(nbq) = 0.0
156c            cpi(nbq) = 0.0
157c         endif
158c         if(i_no2 /= 0) then
159c            nbq = nbq + 1
160c            niq(nbq) = i_no2
161c            aki(nbq) = 0.0
162c            cpi(nbq) = 0.0
163c         endif
164c         if(i_n2d /= 0) then
165c            nbq = nbq + 1
166c            niq(nbq) = i_n2d
167c            aki(nbq) = 0.0
168c            cpi(nbq) = 0.0
169c         endif
170         if (i_he /= 0) then
171            nbq = nbq + 1
172            niq(nbq) = i_he
173            aki(nbq) = 29.9e-4
174            cpi(nbq) = 5.2e3
175         end if
176
177         ! tell the world about it:
178         write(*,*) "concentrations: firstcall, nbq=",nbq
179!         write(*,*) "test M_tr(nbq)=",M_tr(nbq)
180!         write(*,*) "  niq(1:nbq)=",niq(1:nbq)
181!         write(*,*) "  aki(1:nbq)=",aki(1:nbq)
182!         write(*,*) "  cpi(1:nbq)=",cpi(1:nbq)
183         do i = 1,nbq
184            write(*,*) "tname(i)=",tname(i)
185            write(*,*) "tname(niq(i))=",tname(niq(i))
186         end do
187         firstcall = .false.
188      end if ! if (firstcall)
189
190!     update temperature
191
192      do l = 1,klev
193         do ig = 1,klon
194            zt(ig,l) = t_seri(ig,l)
195         end do
196      end do
197
198
199!     update mass mixing ratio tracers
200
201      do l = 1,klev
202         do ig = 1,klon
203            do i = 1,nqmx
204!               iq = niq(i)
205               zq(ig,l,i) = max(1.e-30, tr_seri(ig,l,i))
206            end do
207         end do
208      end do
209
210!     mmean : mean molecular mass
211!     rho   : mass density [kg/m3]
212!     rnew  : specific gas constant
213   
214      mmean(:,:)  = 0.
215      rho(:,:) = 0.     
216
217      do l = 1,klev
218         do ig = 1,klon
219            do i = 1,nqmx-nmicro
220c               iq = niq(i)
221               mmean(ig,l) = mmean(ig,l) + zq(ig,l,i)/M_tr(i)
222            end do
223            mmean(ig,l) = 1./mmean(ig,l)
224            rnew(ig,l) = 8.314/mmean(ig,l)*1.e3     ! J/kg K
225c            write(*,*),'Mmean in concentration2: ',ig, l, mmean(ig,l)
226         end do
227      end do
228
229!     cpnew  : specific heat
230!     akknew : thermal conductivity cofficient
231     
232      cpnew(:,:)  = 0.
233      akknew(:,:) = 0.
234
235      do l = 1,klev
236          do ig = 1,klon
237
238            ntot = pplay(ig,l)/(RKBOL*zt(ig,l))*1.e-6  ! in #/cm3
239            rho(ig,l) = (ntot * mmean(ig,l))/RNAVO*1.e3     ! in kg/m3
240
241c            write(*,*),'Air density: ',ig, l, rho(0,l)           
242
243!!  WARNING -> Cp here below doesn't depend on T (cpdet)
244
245            do i = 1,nbq
246               iq = niq(i)
247               ni(i) = ntot*zq(ig,l,iq)*mmean(ig,l)/M_tr(iq)
248!! On a une super formule pour calculer cp_co2 sur Venus
249               if (iq == i_co2) then
250                  cpnew(ig,l) = cpnew(ig,l) + ni(i)*cpdet(zt(ig,l))
251               else
252                  cpnew(ig,l) = cpnew(ig,l) + ni(i)*cpi(i)
253               end if
254               akknew(ig,l) = akknew(ig,l) + ni(i)*aki(i)
255            end do
256 
257
258            cpnew(ig,l) = cpnew(ig,l)/ntot
259            akknew(ig,l)= akknew(ig,l)/ntot
260
261
262          end do
263       end do
264
265      return
266      end
Note: See TracBrowser for help on using the repository browser.