/[lmdze]/trunk/dyn3d/bilan_dyn.f
ViewVC logotype

Contents of /trunk/dyn3d/bilan_dyn.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 56 - (show annotations)
Tue Jan 10 19:02:02 2012 UTC (12 years, 4 months ago) by guez
Original Path: trunk/libf/dyn3d/bilan_dyn.f90
File size: 12087 byte(s)
Imported "writehist.f" from LMDZ.

Moved module variable "histaveid" from "com_io_dyn" to "initdynav_m".

In "inithist", access directly module variables from "com_io_dyn"
instead of going through the arguments. Copying from LMDZ, write "u"
and scalar variables to separate files. Create a new variable for the
new file in "com_io_dyn". Copying from LMDZ, change the vertical axes
of the three files.

Removed some useless initializations in "dissip".

In "bilan_dyn", removed useless variable "time". Avoiding the
approximate test on "dt_cum" being a multiple of "dt_app", just
compute "ncum" from known usage of "bilan_dyn" and compute "dt_cum"
from "ncum". Change "periodav" from real to integer in
"conf_gcm_m". Since "day_step" is required to be a multiple of
"iperiod", so is "ncum".

1 module bilan_dyn_m
2
3 IMPLICIT NONE
4
5 contains
6
7 SUBROUTINE bilan_dyn(ps, masse, pk, flux_u, flux_v, teta, phi, ucov, vcov, &
8 trac, dt_app)
9
10 ! From LMDZ4/libf/dyn3d/bilan_dyn.F, version 1.5 2005/03/16 10:12:17
11
12 ! Sous-programme consacré à des diagnostics dynamiques de base.
13 ! De façon générale, les moyennes des scalaires Q sont pondérées
14 ! par la masse. Les flux de masse sont, eux, simplement moyennés.
15
16 USE calendar, ONLY: ymds2ju
17 USE conf_gcm_m, ONLY: day_step, iperiod, periodav
18 USE comconst, ONLY: cpp
19 USE comvert, ONLY: presnivs
20 USE comgeom, ONLY: constang_2d, cu_2d, cv_2d, rlatv
21 USE dimens_m, ONLY: iim, jjm, llm
22 USE histcom, ONLY: histbeg_totreg, histdef, histend, histvert
23 USE histwrite_m, ONLY: histwrite
24 USE nr_util, ONLY: pi
25 USE paramet_m, ONLY: iip1, jjp1
26 USE temps, ONLY: annee_ref, day_ref, itau_dyn
27
28 ! Arguments:
29
30 real, intent(in):: ps(iip1, jjp1)
31 real, intent(in):: masse(iip1, jjp1, llm), pk(iip1, jjp1, llm)
32 real, intent(in):: flux_u(iip1, jjp1, llm)
33 real, intent(in):: flux_v(iip1, jjm, llm)
34 real, intent(in):: teta(iip1, jjp1, llm)
35 real, intent(in):: phi(iip1, jjp1, llm)
36 real, intent(in):: ucov(iip1, jjp1, llm)
37 real, intent(in):: vcov(iip1, jjm, llm)
38 real, intent(in):: trac(:, :, :) ! (iim + 1, jjm + 1, llm)
39 real, intent(in):: dt_app
40
41 ! Local:
42
43 real dt_cum
44 integer:: icum = 0
45 integer, save:: ncum
46 logical:: first = .true.
47 real zqy, zfactv(jjm, llm)
48
49 integer, parameter:: nQ = 7
50 character(len=4), parameter:: nom(nQ) = (/'T ', 'gz ', 'K ', 'ang ', &
51 'u ', 'ovap', 'un '/)
52 character(len=5), parameter:: unites(nQ) = (/'K ', 'm2/s2', 'm2/s2', &
53 'ang ', 'm/s ', 'kg/kg', 'un '/)
54
55 integer:: itau = 0
56 real ww
57
58 ! Variables dynamiques intermédiaires
59 REAL vcont(iip1, jjm, llm), ucont(iip1, jjp1, llm)
60 REAL ang(iip1, jjp1, llm), unat(iip1, jjp1, llm)
61 REAL massebx(iip1, jjp1, llm), masseby(iip1, jjm, llm)
62 REAL w(iip1, jjp1, llm), ecin(iip1, jjp1, llm), convm(iip1, jjp1, llm)
63
64 ! Champ contenant les scalaires advectés
65 real Q(iip1, jjp1, llm, nQ)
66
67 ! Champs cumulés
68 real, save:: ps_cum(iip1, jjp1)
69 real, save:: masse_cum(iip1, jjp1, llm)
70 real, save:: flux_u_cum(iip1, jjp1, llm)
71 real, save:: flux_v_cum(iip1, jjm, llm)
72 real, save:: Q_cum(iip1, jjp1, llm, nQ)
73 real, save:: flux_uQ_cum(iip1, jjp1, llm, nQ)
74 real, save:: flux_vQ_cum(iip1, jjm, llm, nQ)
75 real dQ(iip1, jjp1, llm, nQ)
76
77 ! champs de tansport en moyenne zonale
78 integer itr
79 integer, parameter:: ntr = 5
80
81 character(len=10), save:: znom(ntr, nQ)
82 character(len=26), save:: znoml(ntr, nQ)
83 character(len=12), save:: zunites(ntr, nQ)
84
85 integer, parameter:: iave = 1, itot = 2, immc = 3, itrs = 4, istn = 5
86 character(len=3), parameter:: ctrs(ntr) = (/' ', 'TOT', 'MMC', 'TRS', &
87 'STN'/)
88
89 real zvQ(jjm, llm, ntr, nQ), zvQtmp(jjm, llm)
90 real zavQ(jjm, 2: ntr, nQ), psiQ(jjm, llm + 1, nQ)
91 real zmasse(jjm, llm)
92 real zv(jjm, llm), psi(jjm, llm + 1)
93 integer i, j, l, iQ
94
95 ! Initialisation du fichier contenant les moyennes zonales.
96
97 integer, save:: fileid
98 integer thoriid, zvertiid
99
100 real zjulian
101 integer zan, dayref
102
103 real rlong(jjm), rlatg(jjm)
104
105 !-----------------------------------------------------------------
106
107 !!print *, "Call sequence information: bilan_dyn"
108
109 first_call: if (first) then
110 ! initialisation des fichiers
111 first = .false.
112 ! ncum est la frequence de stokage en pas de temps
113 ncum = day_step / iperiod * periodav
114 dt_cum = ncum * dt_app
115
116 ! Initialisation du fichier contenant les moyennes zonales
117
118 zan = annee_ref
119 dayref = day_ref
120 CALL ymds2ju(zan, 1, dayref, 0.0, zjulian)
121
122 rlong = 0.
123 rlatg = rlatv*180./pi
124
125 call histbeg_totreg('dynzon', rlong(:1), rlatg, 1, 1, 1, jjm, itau_dyn, &
126 zjulian, dt_cum, thoriid, fileid)
127
128 ! Appel à histvert pour la grille verticale
129
130 call histvert(fileid, 'presnivs', 'Niveaux sigma', 'mb', llm, presnivs, &
131 zvertiid)
132
133 ! Appels à histdef pour la définition des variables à sauvegarder
134 do iQ = 1, nQ
135 do itr = 1, ntr
136 if (itr == 1) then
137 znom(itr, iQ) = nom(iQ)
138 znoml(itr, iQ) = nom(iQ)
139 zunites(itr, iQ) = unites(iQ)
140 else
141 znom(itr, iQ) = ctrs(itr)//'v'//nom(iQ)
142 znoml(itr, iQ) = 'transport : v * '//nom(iQ)//' '//ctrs(itr)
143 zunites(itr, iQ) = 'm/s * '//unites(iQ)
144 endif
145 enddo
146 enddo
147
148 ! Déclarations des champs avec dimension verticale
149 do iQ = 1, nQ
150 do itr = 1, ntr
151 call histdef(fileid, znom(itr, iQ), znoml(itr, iQ), &
152 zunites(itr, iQ), 1, jjm, thoriid, llm, 1, llm, zvertiid, &
153 'ave(X)', dt_cum, dt_cum)
154 enddo
155 ! Déclarations pour les fonctions de courant
156 call histdef(fileid, 'psi'//nom(iQ), 'stream fn. '//znoml(itot, iQ), &
157 zunites(itot, iQ), 1, jjm, thoriid, llm, 1, llm, zvertiid, &
158 'ave(X)', dt_cum, dt_cum)
159 enddo
160
161 ! Déclarations pour les champs de transport d'air
162 call histdef(fileid, 'masse', 'masse', &
163 'kg', 1, jjm, thoriid, llm, 1, llm, zvertiid, &
164 'ave(X)', dt_cum, dt_cum)
165 call histdef(fileid, 'v', 'v', &
166 'm/s', 1, jjm, thoriid, llm, 1, llm, zvertiid, &
167 'ave(X)', dt_cum, dt_cum)
168 ! Déclarations pour les fonctions de courant
169 call histdef(fileid, 'psi', 'stream fn. MMC ', 'mega t/s', &
170 1, jjm, thoriid, llm, 1, llm, zvertiid, &
171 'ave(X)', dt_cum, dt_cum)
172
173 ! Déclaration des champs 1D de transport en latitude
174 do iQ = 1, nQ
175 do itr = 2, ntr
176 call histdef(fileid, 'a'//znom(itr, iQ), znoml(itr, iQ), &
177 zunites(itr, iQ), 1, jjm, thoriid, 1, 1, 1, -99, &
178 'ave(X)', dt_cum, dt_cum)
179 enddo
180 enddo
181
182 CALL histend(fileid)
183 endif first_call
184
185 itau = itau + 1
186
187 ! Calcul des champs dynamiques
188
189 ! Énergie cinétique
190 ucont = 0
191 CALL covcont(llm, ucov, vcov, ucont, vcont)
192 CALL enercin(vcov, ucov, vcont, ucont, ecin)
193
194 ! moment cinétique
195 do l = 1, llm
196 ang(:, :, l) = ucov(:, :, l) + constang_2d
197 unat(:, :, l) = ucont(:, :, l)*cu_2d
198 enddo
199
200 Q(:, :, :, 1) = teta * pk / cpp
201 Q(:, :, :, 2) = phi
202 Q(:, :, :, 3) = ecin
203 Q(:, :, :, 4) = ang
204 Q(:, :, :, 5) = unat
205 Q(:, :, :, 6) = trac
206 Q(:, :, :, 7) = 1.
207
208 ! Cumul
209
210 if (icum == 0) then
211 ps_cum = 0.
212 masse_cum = 0.
213 flux_u_cum = 0.
214 flux_v_cum = 0.
215 Q_cum = 0.
216 flux_vQ_cum = 0.
217 flux_uQ_cum = 0.
218 endif
219
220 icum = icum + 1
221
222 ! Accumulation des flux de masse horizontaux
223 ps_cum = ps_cum + ps
224 masse_cum = masse_cum + masse
225 flux_u_cum = flux_u_cum + flux_u
226 flux_v_cum = flux_v_cum + flux_v
227 do iQ = 1, nQ
228 Q_cum(:, :, :, iQ) = Q_cum(:, :, :, iQ) + Q(:, :, :, iQ)*masse
229 enddo
230
231 ! FLUX ET TENDANCES
232
233 ! Flux longitudinal
234 forall (iQ = 1: nQ, i = 1: iim) flux_uQ_cum(i, :, :, iQ) &
235 = flux_uQ_cum(i, :, :, iQ) &
236 + flux_u(i, :, :) * 0.5 * (Q(i, :, :, iQ) + Q(i + 1, :, :, iQ))
237 flux_uQ_cum(iip1, :, :, :) = flux_uQ_cum(1, :, :, :)
238
239 ! Flux méridien
240 forall (iQ = 1: nQ, j = 1: jjm) flux_vQ_cum(:, j, :, iQ) &
241 = flux_vQ_cum(:, j, :, iQ) &
242 + flux_v(:, j, :) * 0.5 * (Q(:, j, :, iQ) + Q(:, j + 1, :, iQ))
243
244 ! tendances
245
246 ! convergence horizontale
247 call convflu(flux_uQ_cum, flux_vQ_cum, llm*nQ, dQ)
248
249 ! calcul de la vitesse verticale
250 call convmas(flux_u_cum, flux_v_cum, convm)
251 CALL vitvert(convm, w)
252
253 do iQ = 1, nQ
254 do l = 1, llm-1
255 do j = 1, jjp1
256 do i = 1, iip1
257 ww = -0.5*w(i, j, l + 1)*(Q(i, j, l, iQ) + Q(i, j, l + 1, iQ))
258 dQ(i, j, l, iQ) = dQ(i, j, l, iQ)-ww
259 dQ(i, j, l + 1, iQ) = dQ(i, j, l + 1, iQ) + ww
260 enddo
261 enddo
262 enddo
263 enddo
264
265 ! PAS DE TEMPS D'ECRITURE
266
267 writing_step: if (icum == ncum) then
268 ! Normalisation
269 do iQ = 1, nQ
270 Q_cum(:, :, :, iQ) = Q_cum(:, :, :, iQ)/masse_cum
271 enddo
272 ps_cum = ps_cum / ncum
273 masse_cum = masse_cum / ncum
274 flux_u_cum = flux_u_cum / ncum
275 flux_v_cum = flux_v_cum / ncum
276 flux_uQ_cum = flux_uQ_cum / ncum
277 flux_vQ_cum = flux_vQ_cum / ncum
278 dQ = dQ / ncum
279
280 ! A retravailler eventuellement
281 ! division de dQ par la masse pour revenir aux bonnes grandeurs
282 do iQ = 1, nQ
283 dQ(:, :, :, iQ) = dQ(:, :, :, iQ)/masse_cum
284 enddo
285
286 ! Transport méridien
287
288 ! cumul zonal des masses des mailles
289
290 zv = 0.
291 zmasse = 0.
292 call massbar(masse_cum, massebx, masseby)
293 do l = 1, llm
294 do j = 1, jjm
295 do i = 1, iim
296 zmasse(j, l) = zmasse(j, l) + masseby(i, j, l)
297 zv(j, l) = zv(j, l) + flux_v_cum(i, j, l)
298 enddo
299 zfactv(j, l) = cv_2d(1, j)/zmasse(j, l)
300 enddo
301 enddo
302
303 ! Transport dans le plan latitude-altitude
304
305 zvQ = 0.
306 psiQ = 0.
307 do iQ = 1, nQ
308 zvQtmp = 0.
309 do l = 1, llm
310 do j = 1, jjm
311 ! Calcul des moyennes zonales du transort total et de zvQtmp
312 do i = 1, iim
313 zvQ(j, l, itot, iQ) = zvQ(j, l, itot, iQ) &
314 + flux_vQ_cum(i, j, l, iQ)
315 zqy = 0.5 * (Q_cum(i, j, l, iQ) * masse_cum(i, j, l) &
316 + Q_cum(i, j + 1, l, iQ) * masse_cum(i, j + 1, l))
317 zvQtmp(j, l) = zvQtmp(j, l) + flux_v_cum(i, j, l) * zqy &
318 / (0.5 * (masse_cum(i, j, l) + masse_cum(i, j + 1, l)))
319 zvQ(j, l, iave, iQ) = zvQ(j, l, iave, iQ) + zqy
320 enddo
321 ! Decomposition
322 zvQ(j, l, iave, iQ) = zvQ(j, l, iave, iQ)/zmasse(j, l)
323 zvQ(j, l, itot, iQ) = zvQ(j, l, itot, iQ)*zfactv(j, l)
324 zvQtmp(j, l) = zvQtmp(j, l)*zfactv(j, l)
325 zvQ(j, l, immc, iQ) = zv(j, l)*zvQ(j, l, iave, iQ)*zfactv(j, l)
326 zvQ(j, l, itrs, iQ) = zvQ(j, l, itot, iQ)-zvQtmp(j, l)
327 zvQ(j, l, istn, iQ) = zvQtmp(j, l)-zvQ(j, l, immc, iQ)
328 enddo
329 enddo
330 ! fonction de courant meridienne pour la quantite Q
331 do l = llm, 1, -1
332 do j = 1, jjm
333 psiQ(j, l, iQ) = psiQ(j, l + 1, iQ) + zvQ(j, l, itot, iQ)
334 enddo
335 enddo
336 enddo
337
338 ! fonction de courant pour la circulation meridienne moyenne
339 psi = 0.
340 do l = llm, 1, -1
341 do j = 1, jjm
342 psi(j, l) = psi(j, l + 1) + zv(j, l)
343 zv(j, l) = zv(j, l)*zfactv(j, l)
344 enddo
345 enddo
346
347 ! sorties proprement dites
348 do iQ = 1, nQ
349 do itr = 1, ntr
350 call histwrite(fileid, znom(itr, iQ), itau, zvQ(:, :, itr, iQ))
351 enddo
352 call histwrite(fileid, 'psi'//nom(iQ), itau, psiQ(:, :llm, iQ))
353 enddo
354
355 call histwrite(fileid, 'masse', itau, zmasse)
356 call histwrite(fileid, 'v', itau, zv)
357 psi = psi*1.e-9
358 call histwrite(fileid, 'psi', itau, psi(:, :llm))
359
360 ! Intégrale verticale
361
362 forall (iQ = 1: nQ, itr = 2: ntr) zavQ(:, itr, iQ) &
363 = sum(zvQ(:, :, itr, iQ) * zmasse, dim=2) / cv_2d(1, :)
364
365 do iQ = 1, nQ
366 do itr = 2, ntr
367 call histwrite(fileid, 'a'//znom(itr, iQ), itau, zavQ(:, itr, iQ))
368 enddo
369 enddo
370
371 ! On doit pouvoir tracer systematiquement la fonction de courant.
372 icum = 0
373 endif writing_step
374
375 end SUBROUTINE bilan_dyn
376
377 end module bilan_dyn_m

  ViewVC Help
Powered by ViewVC 1.1.21