1 | SUBROUTINE concentrations(ngrid,nlayer,nq, |
---|
2 | & pplay,pt,pdt,pq,pdq,ptimestep) |
---|
3 | |
---|
4 | use tracer_h, only: mmol, noms, aki, cpi, nesp |
---|
5 | |
---|
6 | use conc_mod, only: mmean, akknew, rnew, cpnew |
---|
7 | USE comcstfi_mod |
---|
8 | use callkeys_mod |
---|
9 | use chimiedata_h |
---|
10 | implicit none |
---|
11 | |
---|
12 | !======================================================================= |
---|
13 | ! CALCULATION OF MEAN MOLECULAR MASS, Cp, Akk and R |
---|
14 | ! |
---|
15 | ! mmean(ngrid,nlayer) amu |
---|
16 | ! cpnew(ngrid,nlayer) J/kg/K |
---|
17 | ! rnew(ngrid,nlayer) J/kg/K |
---|
18 | ! akknew(ngrid,nlayer) coefficient of thermal concduction |
---|
19 | ! |
---|
20 | ! version: April 2012 - Franck Lefevre |
---|
21 | ! update 06/03/2021 cpi/aki input (Yassin Jaziri) |
---|
22 | !======================================================================= |
---|
23 | |
---|
24 | ! input/output |
---|
25 | |
---|
26 | integer,intent(in) :: ngrid ! number of atmospheric columns |
---|
27 | integer,intent(in) :: nlayer ! number of atmospheric layers |
---|
28 | integer,intent(in) :: nq ! number of tracers |
---|
29 | real, intent(in) :: pplay(ngrid,nlayer) |
---|
30 | real, intent(in) :: pt(ngrid,nlayer) |
---|
31 | real, intent(in) :: pdt(ngrid,nlayer) |
---|
32 | real, intent(in) :: pq(ngrid,nlayer,nq) |
---|
33 | real, intent(in) :: pdq(ngrid,nlayer,nq) |
---|
34 | real, intent(in) :: ptimestep |
---|
35 | |
---|
36 | ! local variables |
---|
37 | |
---|
38 | integer :: l, ig, iq |
---|
39 | real :: ni(nq), ntot |
---|
40 | real :: zq(ngrid, nlayer, nq) |
---|
41 | real :: zt(ngrid, nlayer) |
---|
42 | |
---|
43 | ! update temperature |
---|
44 | |
---|
45 | do l = 1,nlayer |
---|
46 | do ig = 1,ngrid |
---|
47 | zt(ig,l) = pt(ig,l) + pdt(ig,l)*ptimestep |
---|
48 | end do |
---|
49 | end do |
---|
50 | |
---|
51 | ! update tracers |
---|
52 | |
---|
53 | do l = 1,nlayer |
---|
54 | do ig = 1,ngrid |
---|
55 | do iq = 1,nq |
---|
56 | zq(ig,l,iq) = max(1.e-30, pq(ig,l,iq) |
---|
57 | $ + pdq(ig,l,iq)*ptimestep) |
---|
58 | end do |
---|
59 | end do |
---|
60 | end do |
---|
61 | |
---|
62 | ! mmean : mean molecular mass |
---|
63 | ! rnew : specific gas constant |
---|
64 | |
---|
65 | mmean(:,:) = 0. |
---|
66 | do l = 1,nlayer |
---|
67 | do ig = 1,ngrid |
---|
68 | do iq = 1,nq |
---|
69 | if (mmol(iq).ne.0.) then |
---|
70 | mmean(ig,l) = mmean(ig,l) + zq(ig,l,iq)/mmol(iq) |
---|
71 | end if |
---|
72 | end do |
---|
73 | mmean(ig,l) = 1./mmean(ig,l) |
---|
74 | rnew(ig,l) = 8.314/mmean(ig,l)*1.e3 ! J/kg/K |
---|
75 | end do |
---|
76 | end do |
---|
77 | |
---|
78 | |
---|
79 | ! cpnew : specicic heat |
---|
80 | ! akknew : thermal conductivity cofficient |
---|
81 | cpnew(:,:) = 0. |
---|
82 | akknew(:,:) = 0. |
---|
83 | |
---|
84 | do l = 1,nlayer |
---|
85 | do ig = 1,ngrid |
---|
86 | ntot = pplay(ig,l)/(1.381e-23*zt(ig,l))*1.e-6 ! in #/cm3 |
---|
87 | do iq = 1,nq |
---|
88 | ni(iq) = ntot*zq(ig,l,iq)*mmean(ig,l)/mmol(iq) |
---|
89 | cpnew(ig,l) = cpnew(ig,l) + ni(iq)*cpi(iq) |
---|
90 | akknew(ig,l) = akknew(ig,l) + ni(iq)*aki(iq) |
---|
91 | end do |
---|
92 | cpnew(ig,l) = cpnew(ig,l)/ntot |
---|
93 | akknew(ig,l) = akknew(ig,l)/ntot |
---|
94 | end do |
---|
95 | end do |
---|
96 | |
---|
97 | return |
---|
98 | end |
---|