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

Last change on this file since 1543 was 1530, checked in by emillour, 9 years ago

Venus and Titan GCMs:
Updates in the physics to keep up with updates in LMDZ5 (up to
LMDZ5 trunk, rev 2350) concerning dynamics/physics separation:

  • Adapted makelmdz and makelmdz_fcm script to stop if trying to compile 1d model or newstart or start2archive in parallel.
  • got rid of references to "dimensions.h" in physics. Within physics packages, use nbp_lon (=iim), nbp_lat (=jjmp1) and nbp_lev (=llm) from module mod_grid_phy_lmdz (in phy_common) instead. Only partially done for Titan, because of many hard-coded commons; a necessary first step will be to clean these up (using modules).

EM

File size: 6.8 KB
Line 
1      SUBROUTINE concentrations2(pplay,t_seri,pdt,tr_seri, nqmx)
2
3      use dimphy
4      use conc,  only: mmean, rho, Akknew, rnew, cpnew
5      use cpdet_mod, only: cpdet                       
6      USE chemparam_mod
7      use infotrac
8
9      implicit none
10
11!=======================================================================
12! CALCULATION OF MEAN MOLECULAR MASS, Cp, Akk and R
13!
14! mmean(klon,klev)      amu
15! cpnew(klon,klev)      J/kg/K
16! rnew(klon,klev)       J/kg/K
17! akknew(klon,klev)     coefficient of thermal conduction
18!
19! version: April 2012 - Franck Lefevre
20!=======================================================================
21
22!     declarations
23 
24#include "YOMCST.h"
25#include "clesphys.h"
26c#include "comdiurn.h"
27c#include "chimiedata.h"
28c#include "tracer.h"
29c#include "mmol.h"
30
31!     input/output
32
33      real pplay(klon,klev)
34c      real pt(klon,klev)
35      integer,intent(in) :: nqmx    ! number of tracers
36      real t_seri(klon, klev)
37      real pdt(klon,klev)
38      real n2vmr_gcm(klon,klev),nvmr_gcm(klon,klev)
39      real tr_seri(klon,klev,nqmx)
40c      real pdq(klon,klev,nqmx)
41      real ptimestep
42
43!     local variables
44
45      integer       :: i, l, ig, iq
46      integer, save :: nbq
47      integer,allocatable,save :: niq(:)
48      real          :: ni(nqmx), ntot
49      real          :: zt(klon, klev)
50      real          :: zq(klon, klev, nqmx)
51      real,allocatable,save    :: aki(:)
52      real,allocatable,save    :: cpi(:)
53      real, save    :: akin,akin2
54
55      logical, save :: firstcall = .true.
56
57      if (firstcall) then
58
59!        initialize thermal conductivity and specific heat coefficients
60!        values are taken from the literature [J/kg K]
61
62         ! allocate local saved arrays:
63         allocate(aki(nqmx))
64         allocate(cpi(nqmx))
65         allocate(niq(nqmx))
66
67!        find index of chemical tracers to use
68!        initialize thermal conductivity and specific heat coefficients
69!        !? values are estimated
70
71         nbq = 0 ! to count number of tracers used in this subroutine
72
73         if (i_co2 /= 0) then
74            nbq = nbq + 1
75            niq(nbq) = i_co2
76            aki(nbq) = 3.072e-4
77            cpi(nbq) = 0.834e3
78         end if
79         if (i_co /= 0) then
80            nbq = nbq + 1
81            niq(nbq) = i_co
82            aki(nbq) = 4.87e-4
83            cpi(nbq) = 1.034e3
84         end if
85         if (i_o /= 0) then
86            nbq = nbq + 1
87            niq(nbq) = i_o
88            aki(nbq) = 7.59e-4
89            cpi(nbq) = 1.3e3
90         end if
91         if (i_o1d /= 0) then
92            nbq = nbq + 1
93            niq(nbq) = i_o1d
94            aki(nbq) = 7.59e-4  !?
95            cpi(nbq) = 1.3e3    !?
96         end if
97         if (i_o2 /= 0) then
98            nbq = nbq + 1
99            niq(nbq) = i_o2
100            aki(nbq) = 5.68e-4
101            cpi(nbq) = 0.9194e3
102         end if
103         if (i_o3 /= 0) then
104            nbq = nbq + 1
105            niq(nbq) = i_o3
106            aki(nbq) = 3.00e-4  !?
107            cpi(nbq) = 0.800e3  !?
108         end if
109         if (i_h /= 0) then
110            nbq = nbq + 1
111            niq(nbq) = i_h
112            aki(nbq) = 0.0
113            cpi(nbq) = 20.780e3
114         end if
115         if (i_h2 /= 0) then
116            nbq = nbq + 1
117            niq(nbq) = i_h2
118            aki(nbq) = 36.314e-4
119            cpi(nbq) = 14.266e3
120         end if
121         if (i_oh /= 0) then
122            nbq = nbq + 1
123            niq(nbq) = i_oh
124            aki(nbq)  = 7.00e-4 !?
125            cpi(nbq)  = 1.045e3
126         end if
127         if (i_ho2 /= 0) then
128            nbq = nbq + 1
129            niq(nbq) = i_ho2
130            aki(nbq) = 0.0
131            cpi(nbq) = 1.065e3  !?
132         end if
133         if (i_n2 /= 0) then
134            nbq = nbq + 1
135            niq(nbq) = i_n2
136            aki(nbq) = 5.6e-4
137            cpi(nbq) = 1.034e3
138         end if
139c         if (i_ar /= 0) then
140c            nbq = nbq + 1
141c            niq(nbq) = i_ar
142c            aki(nbq) = 0.0      !?
143c            cpi(nbq) = 1.000e3  !?
144c         end if
145         if (i_h2o /= 0) then
146            nbq = nbq + 1
147            niq(nbq) = i_h2o
148            aki(nbq) = 0.0
149            cpi(nbq) = 1.870e3
150         end if
151c         if (i_n /= 0) then
152c            nbq = nbq + 1
153c            niq(nbq) = i_n
154c            aki(nbq) = 0.0
155c            cpi(nbq) = 0.0
156c         endif
157c         if(i_no /= 0) then
158c            nbq = nbq + 1
159c            niq(nbq) = i_no
160c            aki(nbq) = 0.0
161c            cpi(nbq) = 0.0
162c         endif
163c         if(i_no2 /= 0) then
164c            nbq = nbq + 1
165c            niq(nbq) = i_no2
166c            aki(nbq) = 0.0
167c            cpi(nbq) = 0.0
168c         endif
169c         if(i_n2d /= 0) then
170c            nbq = nbq + 1
171c            niq(nbq) = i_n2d
172c            aki(nbq) = 0.0
173c            cpi(nbq) = 0.0
174c         endif
175
176  !     n2
177c            akin2 = 5.6e-4
178c            cpin2 = 1.034e3
179
180
181         
182         ! tell the world about it:
183         write(*,*) "concentrations: firstcall, nbq=",nbq
184!         write(*,*) "  niq(1:nbq)=",niq(1:nbq)
185!         write(*,*) "  aki(1:nbq)=",aki(1:nbq)
186!         write(*,*) "  cpi(1:nbq)=",cpi(1:nbq)
187
188
189         firstcall = .false.
190      end if ! if (firstcall)
191
192!     update temperature
193
194      do l = 1,klev
195         do ig = 1,klon
196            zt(ig,l) = t_seri(ig,l)
197         end do
198      end do
199
200
201!     update mass mixing ratio tracers
202
203      do l = 1,klev
204         do ig = 1,klon
205            do i = 1,nqmx
206!               iq = niq(i)
207               zq(ig,l,i) = max(1.e-30, tr_seri(ig,l,i))
208            end do
209         end do
210      end do
211
212!     mmean : mean molecular mass
213!     rho   : mass density [kg/m3]
214!     rnew  : specific gas constant
215   
216      mmean(:,:)  = 0.
217      rho(:,:) = 0.     
218
219      do l = 1,klev
220         do ig = 1,klon
221            do i = 1,nqmx
222c               iq = niq(i)
223               mmean(ig,l) = mmean(ig,l) + zq(ig,l,i)/M_tr(i)
224            end do
225            mmean(ig,l) = 1./mmean(ig,l)
226            rnew(ig,l) = 8.314/mmean(ig,l)*1.e3     ! J/kg K           
227 
228c            write(*,*),'Mmean: ',ig, l, mmean(ig,l)
229         end do
230      end do
231
232!     cpnew  : specific heat
233!     akknew : thermal conductivity cofficient
234     
235      cpnew(:,:)  = 0.
236      akknew(:,:) = 0.
237
238      do l = 1,klev
239          do ig = 1,klon
240
241            ntot = pplay(ig,l)/(RKBOL*zt(ig,l))*1.e-6  ! in #/cm3
242            rho(ig,l) = (ntot * mmean(ig,l))/RNAVO*1.e3     ! in kg/m3
243
244c            write(*,*),'Air density: ',ig, l, rho(0,l)           
245
246!!! --- INSERT N2 values ----
247!!  WARNING -> Cp here below doesn't depend on T (cpdet)
248
249            do i = 1,nbq
250c               iq = niq(i)
251               ni(i) = ntot*zq(ig,l,i)*mmean(ig,l)/M_tr(i)
252               cpnew(ig,l) = cpnew(ig,l) + ni(i)*cpi(i)
253               akknew(ig,l) = akknew(ig,l) + ni(i)*aki(i)
254            end do
255 
256
257            cpnew(ig,l) = cpnew(ig,l)/ntot
258            akknew(ig,l)= akknew(ig,l)/ntot
259
260
261          end do
262       end do
263
264      return
265      end
Note: See TracBrowser for help on using the repository browser.