/[lmdze]/trunk/Sources/phylmd/phystokenc.f
ViewVC logotype

Contents of /trunk/Sources/phylmd/phystokenc.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 190 - (show annotations)
Thu Apr 14 15:15:56 2016 UTC (8 years, 1 month ago) by guez
File size: 8803 byte(s)
Created module cv_thermo_m around procedure cv_thermo. Moved variables
from module cvthermo to module cv_thermo_m, where they are defined.

In ini_histins and initphysto, using part of rlon and rlat from
phyetat0_m is pretending that we do not know about the dynamical grid,
while the way we extract zx_lon(:, 1) and zx_lat(1, :) depends on
ordering inside rlon and rlat. So we might as well simplify and
clarify by using directly rlonv and rlatu.

Removed intermediary variables in write_histins and phystokenc.

1 module phystokenc_m
2
3 IMPLICIT NONE
4
5 contains
6
7 SUBROUTINE phystokenc(pdtphys, pt, pmfu, pmfd, pen_u, pde_u, pen_d, pde_d, &
8 pfm_therm, pentr_therm, pcoefh, yu1, yv1, ftsol, pctsrf, frac_impa, &
9 frac_nucl, pphis, paire, dtime, itap)
10
11 ! From phylmd/phystokenc.F, version 1.2 2004/06/22 11:45:35
12 ! Author: Fr\'ed\'eric Hourdin
13 ! Objet : \'ecriture des variables pour transport offline
14
15 use gr_phy_write_m, only: gr_phy_write
16 USE histwrite_m, ONLY: histwrite
17 USE histsync_m, ONLY: histsync
18 USE dimens_m, ONLY: iim, jjm
19 USE indicesol, ONLY: nbsrf
20 use initphysto_m, only: initphysto
21 USE dimphy, ONLY: klev, klon
22 USE tracstoke, ONLY: istphy
23
24 REAL, INTENT (IN):: pdtphys ! pas d'integration pour la physique (seconde)
25 REAL, intent(in):: pt(klon, klev)
26
27 ! convection:
28
29 REAL, INTENT (IN):: pmfu(klon, klev) ! flux de masse dans le panache montant
30
31 REAL, intent(in):: pmfd(klon, klev)
32 ! flux de masse dans le panache descendant
33
34 REAL, intent(in):: pen_u(klon, klev) ! flux entraine dans le panache montant
35 REAL, intent(in):: pde_u(klon, klev) ! flux detraine dans le panache montant
36
37 REAL, intent(in):: pen_d(klon, klev)
38 ! flux entraine dans le panache descendant
39
40 REAL, intent(in):: pde_d(klon, klev)
41 ! flux detraine dans le panache descendant
42
43 ! Les Thermiques
44 REAL pfm_therm(klon, klev+1)
45 REAL pentr_therm(klon, klev)
46
47 ! Couche limite:
48
49 REAL pcoefh(klon, klev) ! coeff melange Couche limite
50 REAL yu1(klon)
51 REAL yv1(klon)
52
53 ! Arguments necessaires pour les sources et puits de traceur
54
55 REAL ftsol(klon, nbsrf) ! Temperature du sol (surf)(Kelvin)
56 REAL pctsrf(klon, nbsrf) ! Pourcentage de sol f(nature du sol)
57
58 ! Lessivage:
59
60 REAL frac_impa(klon, klev)
61 REAL frac_nucl(klon, klev)
62
63 REAL, INTENT(IN):: pphis(klon)
64 real paire(klon)
65 REAL, INTENT (IN):: dtime
66 INTEGER, INTENT (IN):: itap
67
68 ! Variables local to the procedure:
69
70 real t(klon, klev)
71 INTEGER, SAVE:: physid
72
73 ! Les Thermiques
74
75 REAL fm_therm1(klon, klev)
76 REAL entr_therm(klon, klev)
77 REAL fm_therm(klon, klev)
78
79 INTEGER i, k
80
81 REAL, save:: mfu(klon, klev) ! flux de masse dans le panache montant
82 REAL mfd(klon, klev) ! flux de masse dans le panache descendant
83 REAL en_u(klon, klev) ! flux entraine dans le panache montant
84 REAL de_u(klon, klev) ! flux detraine dans le panache montant
85 REAL en_d(klon, klev) ! flux entraine dans le panache descendant
86 REAL de_d(klon, klev) ! flux detraine dans le panache descendant
87 REAL coefh(klon, klev) ! flux detraine dans le panache descendant
88
89 REAL pyu1(klon), pyv1(klon)
90 REAL pftsol(klon, nbsrf), ppsrf(klon, nbsrf)
91 REAL pftsol1(klon), pftsol2(klon), pftsol3(klon), pftsol4(klon)
92 REAL ppsrf1(klon), ppsrf2(klon), ppsrf3(klon), ppsrf4(klon)
93
94 REAL dtcum
95
96 INTEGER:: iadvtr = 0, irec = 1
97 REAL zmin, zmax
98 LOGICAL ok_sync
99
100 SAVE t, mfd, en_u, de_u, en_d, de_d, coefh, dtcum
101 SAVE fm_therm, entr_therm
102 SAVE pyu1, pyv1, pftsol, ppsrf
103
104 !------------------------------------------------------
105
106 ! Couche limite:
107
108 ok_sync = .TRUE.
109
110 IF (iadvtr==0) CALL initphysto('phystoke', dtime, dtime*istphy, dtime*istphy, physid)
111
112 i = itap
113 CALL histwrite(physid, 'phis', i, gr_phy_write(pphis))
114 i = itap
115 CALL histwrite(physid, 'aire', i, gr_phy_write(paire))
116 iadvtr = iadvtr + 1
117
118 IF (mod(iadvtr, istphy) == 1 .OR. istphy == 1) THEN
119 PRINT *, 'reinitialisation des champs cumules a iadvtr =', iadvtr
120 DO k = 1, klev
121 DO i = 1, klon
122 mfu(i, k) = 0.
123 mfd(i, k) = 0.
124 en_u(i, k) = 0.
125 de_u(i, k) = 0.
126 en_d(i, k) = 0.
127 de_d(i, k) = 0.
128 coefh(i, k) = 0.
129 t(i, k) = 0.
130 fm_therm(i, k) = 0.
131 entr_therm(i, k) = 0.
132 END DO
133 END DO
134 DO i = 1, klon
135 pyv1(i) = 0.
136 pyu1(i) = 0.
137 END DO
138 DO k = 1, nbsrf
139 DO i = 1, klon
140 pftsol(i, k) = 0.
141 ppsrf(i, k) = 0.
142 END DO
143 END DO
144
145 dtcum = 0.
146 END IF
147
148 DO k = 1, klev
149 DO i = 1, klon
150 mfu(i, k) = mfu(i, k) + pmfu(i, k)*pdtphys
151 mfd(i, k) = mfd(i, k) + pmfd(i, k)*pdtphys
152 en_u(i, k) = en_u(i, k) + pen_u(i, k)*pdtphys
153 de_u(i, k) = de_u(i, k) + pde_u(i, k)*pdtphys
154 en_d(i, k) = en_d(i, k) + pen_d(i, k)*pdtphys
155 de_d(i, k) = de_d(i, k) + pde_d(i, k)*pdtphys
156 coefh(i, k) = coefh(i, k) + pcoefh(i, k)*pdtphys
157 t(i, k) = t(i, k) + pt(i, k)*pdtphys
158 fm_therm(i, k) = fm_therm(i, k) + pfm_therm(i, k)*pdtphys
159 entr_therm(i, k) = entr_therm(i, k) + pentr_therm(i, k)*pdtphys
160 END DO
161 END DO
162 DO i = 1, klon
163 pyv1(i) = pyv1(i) + yv1(i)*pdtphys
164 pyu1(i) = pyu1(i) + yu1(i)*pdtphys
165 END DO
166 DO k = 1, nbsrf
167 DO i = 1, klon
168 pftsol(i, k) = pftsol(i, k) + ftsol(i, k)*pdtphys
169 ppsrf(i, k) = ppsrf(i, k) + pctsrf(i, k)*pdtphys
170 END DO
171 END DO
172
173 dtcum = dtcum + pdtphys
174
175 IF (mod(iadvtr, istphy) == 0) THEN
176 ! normalisation par le temps cumule
177 DO k = 1, klev
178 DO i = 1, klon
179 mfu(i, k) = mfu(i, k)/dtcum
180 mfd(i, k) = mfd(i, k)/dtcum
181 en_u(i, k) = en_u(i, k)/dtcum
182 de_u(i, k) = de_u(i, k)/dtcum
183 en_d(i, k) = en_d(i, k)/dtcum
184 de_d(i, k) = de_d(i, k)/dtcum
185 coefh(i, k) = coefh(i, k)/dtcum
186 ! Unitel a enlever
187 t(i, k) = t(i, k)/dtcum
188 fm_therm(i, k) = fm_therm(i, k)/dtcum
189 entr_therm(i, k) = entr_therm(i, k)/dtcum
190 END DO
191 END DO
192 DO i = 1, klon
193 pyv1(i) = pyv1(i)/dtcum
194 pyu1(i) = pyu1(i)/dtcum
195 END DO
196 DO k = 1, nbsrf
197 DO i = 1, klon
198 pftsol(i, k) = pftsol(i, k)/dtcum
199 pftsol1(i) = pftsol(i, 1)
200 pftsol2(i) = pftsol(i, 2)
201 pftsol3(i) = pftsol(i, 3)
202 pftsol4(i) = pftsol(i, 4)
203
204 ppsrf(i, k) = ppsrf(i, k)/dtcum
205 ppsrf1(i) = ppsrf(i, 1)
206 ppsrf2(i) = ppsrf(i, 2)
207 ppsrf3(i) = ppsrf(i, 3)
208 ppsrf4(i) = ppsrf(i, 4)
209 END DO
210 END DO
211
212 ! ecriture des champs
213
214 irec = irec + 1
215
216 CALL histwrite(physid, 't', itap, gr_phy_write(t))
217 CALL histwrite(physid, 'mfu', itap, gr_phy_write(mfu))
218 CALL histwrite(physid, 'mfd', itap, gr_phy_write(mfd))
219 CALL histwrite(physid, 'en_u', itap, gr_phy_write(en_u))
220 CALL histwrite(physid, 'de_u', itap, gr_phy_write(de_u))
221 CALL histwrite(physid, 'en_d', itap, gr_phy_write(en_d))
222 CALL histwrite(physid, 'de_d', itap, gr_phy_write(de_d))
223 CALL histwrite(physid, 'coefh', itap, gr_phy_write(coefh))
224 DO k = 1, klev
225 DO i = 1, klon
226 fm_therm1(i, k) = fm_therm(i, k)
227 END DO
228 END DO
229
230 CALL histwrite(physid, 'fm_th', itap, gr_phy_write(fm_therm1))
231 CALL histwrite(physid, 'en_th', itap, gr_phy_write(entr_therm))
232 !ccc
233 CALL histwrite(physid, 'frac_impa', itap, gr_phy_write(frac_impa))
234 CALL histwrite(physid, 'frac_nucl', itap, gr_phy_write(frac_nucl))
235 CALL histwrite(physid, 'pyu1', itap, gr_phy_write(pyu1))
236 CALL histwrite(physid, 'pyv1', itap, gr_phy_write(pyv1))
237 CALL histwrite(physid, 'ftsol1', itap, gr_phy_write(pftsol1))
238 CALL histwrite(physid, 'ftsol2', itap, gr_phy_write(pftsol2))
239 CALL histwrite(physid, 'ftsol3', itap, gr_phy_write(pftsol3))
240 CALL histwrite(physid, 'ftsol4', itap, gr_phy_write(pftsol4))
241 CALL histwrite(physid, 'psrf1', itap, gr_phy_write(ppsrf1))
242 CALL histwrite(physid, 'psrf2', itap, gr_phy_write(ppsrf2))
243 CALL histwrite(physid, 'psrf3', itap, gr_phy_write(ppsrf3))
244 CALL histwrite(physid, 'psrf4', itap, gr_phy_write(ppsrf4))
245 IF (ok_sync) CALL histsync(physid)
246
247 ! Test sur la valeur des coefficients de lessivage
248
249 zmin = 1E33
250 zmax = -1E33
251 DO k = 1, klev
252 DO i = 1, klon
253 zmax = max(zmax, frac_nucl(i, k))
254 zmin = min(zmin, frac_nucl(i, k))
255 END DO
256 END DO
257 PRINT *, 'coefs de lessivage (min et max)'
258 PRINT *, 'facteur de nucleation ', zmin, zmax
259 zmin = 1E33
260 zmax = -1E33
261 DO k = 1, klev
262 DO i = 1, klon
263 zmax = max(zmax, frac_impa(i, k))
264 zmin = min(zmin, frac_impa(i, k))
265 END DO
266 END DO
267 PRINT *, 'facteur d impaction ', zmin, zmax
268 END IF
269
270 END SUBROUTINE phystokenc
271
272 end module phystokenc_m

  ViewVC Help
Powered by ViewVC 1.1.21