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

Contents of /trunk/dyn3d/bilan_dyn.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 82 - (show annotations)
Wed Mar 5 14:57:53 2014 UTC (10 years, 2 months ago) by guez
File size: 7186 byte(s)
Changed all ".f90" suffixes to ".f".
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)
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 comconst, ONLY: cpp
17 USE comgeom, ONLY: constang_2d, cu_2d, cv_2d
18 USE dimens_m, ONLY: iim, jjm, llm
19 USE histwrite_m, ONLY: histwrite
20 use init_dynzon_m, only: ncum, fileid, znom, ntr, nq, nom
21 USE paramet_m, ONLY: iip1, jjp1
22
23 real, intent(in):: ps(iip1, jjp1)
24 real, intent(in):: masse(iip1, jjp1, llm), pk(iip1, jjp1, llm)
25 real, intent(in):: flux_u(iip1, jjp1, llm)
26 real, intent(in):: flux_v(iip1, jjm, llm)
27 real, intent(in):: teta(iip1, jjp1, llm)
28 real, intent(in):: phi(iip1, jjp1, llm)
29 real, intent(in):: ucov(:, :, :) ! (iip1, jjp1, llm)
30 real, intent(in):: vcov(iip1, jjm, llm)
31 real, intent(in):: trac(:, :, :) ! (iim + 1, jjm + 1, llm)
32
33 ! Local:
34
35 integer:: icum = 0
36 integer:: itau = 0
37 real qy, factv(jjm, llm)
38
39 ! Variables dynamiques intermédiaires
40 REAL vcont(iip1, jjm, llm), ucont(iip1, jjp1, llm)
41 REAL ang(iip1, jjp1, llm), unat(iip1, jjp1, llm)
42 REAL massebx(iip1, jjp1, llm), masseby(iip1, jjm, llm)
43 REAL ecin(iip1, jjp1, llm)
44
45 ! Champ contenant les scalaires advectés
46 real Q(iip1, jjp1, llm, nQ)
47
48 ! Champs cumulés
49 real, save:: ps_cum(iip1, jjp1)
50 real, save:: masse_cum(iip1, jjp1, llm)
51 real, save:: flux_u_cum(iip1, jjp1, llm)
52 real, save:: flux_v_cum(iip1, jjm, llm)
53 real, save:: Q_cum(iip1, jjp1, llm, nQ)
54 real, save:: flux_uQ_cum(iip1, jjp1, llm, nQ)
55 real, save:: flux_vQ_cum(iip1, jjm, llm, nQ)
56
57 ! champs de tansport en moyenne zonale
58 integer itr
59 integer, parameter:: iave = 1, itot = 2, immc = 3, itrs = 4, istn = 5
60
61 real vq(jjm, llm, ntr, nQ), vqtmp(jjm, llm)
62 real avq(jjm, 2: ntr, nQ), psiQ(jjm, llm + 1, nQ)
63 real zmasse(jjm, llm)
64 real v(jjm, llm), psi(jjm, llm + 1)
65 integer i, j, l, iQ
66
67 !-----------------------------------------------------------------
68
69 ! Calcul des champs dynamiques
70
71 ! Énergie cinétique
72 ucont = 0
73 CALL covcont(llm, ucov, vcov, ucont, vcont)
74 CALL enercin(vcov, ucov, vcont, ucont, ecin)
75
76 ! moment cinétique
77 forall (l = 1: llm)
78 ang(:, :, l) = ucov(:, :, l) + constang_2d
79 unat(:, :, l) = ucont(:, :, l) * cu_2d
80 end forall
81
82 Q(:, :, :, 1) = teta * pk / cpp
83 Q(:, :, :, 2) = phi
84 Q(:, :, :, 3) = ecin
85 Q(:, :, :, 4) = ang
86 Q(:, :, :, 5) = unat
87 Q(:, :, :, 6) = trac
88 Q(:, :, :, 7) = 1.
89
90 ! Cumul
91
92 if (icum == 0) then
93 ps_cum = 0.
94 masse_cum = 0.
95 flux_u_cum = 0.
96 flux_v_cum = 0.
97 Q_cum = 0.
98 flux_vQ_cum = 0.
99 flux_uQ_cum = 0.
100 endif
101
102 itau = itau + 1
103 icum = icum + 1
104
105 ! Accumulation des flux de masse horizontaux
106 ps_cum = ps_cum + ps
107 masse_cum = masse_cum + masse
108 flux_u_cum = flux_u_cum + flux_u
109 flux_v_cum = flux_v_cum + flux_v
110 forall (iQ = 1: nQ) Q_cum(:, :, :, iQ) = Q_cum(:, :, :, iQ) &
111 + Q(:, :, :, iQ) * masse
112
113 ! Flux longitudinal
114 forall (iQ = 1: nQ, i = 1: iim) flux_uQ_cum(i, :, :, iQ) &
115 = flux_uQ_cum(i, :, :, iQ) &
116 + flux_u(i, :, :) * 0.5 * (Q(i, :, :, iQ) + Q(i + 1, :, :, iQ))
117 flux_uQ_cum(iip1, :, :, :) = flux_uQ_cum(1, :, :, :)
118
119 ! Flux méridien
120 forall (iQ = 1: nQ, j = 1: jjm) flux_vQ_cum(:, j, :, iQ) &
121 = flux_vQ_cum(:, j, :, iQ) &
122 + flux_v(:, j, :) * 0.5 * (Q(:, j, :, iQ) + Q(:, j + 1, :, iQ))
123
124 writing_step: if (icum == ncum) then
125 ! Normalisation
126 forall (iQ = 1: nQ) Q_cum(:, :, :, iQ) = Q_cum(:, :, :, iQ) / masse_cum
127 ps_cum = ps_cum / ncum
128 masse_cum = masse_cum / ncum
129 flux_u_cum = flux_u_cum / ncum
130 flux_v_cum = flux_v_cum / ncum
131 flux_uQ_cum = flux_uQ_cum / ncum
132 flux_vQ_cum = flux_vQ_cum / ncum
133
134 ! Transport méridien
135
136 ! Cumul zonal des masses des mailles
137
138 v = 0.
139 zmasse = 0.
140 call massbar(masse_cum, massebx, masseby)
141 do l = 1, llm
142 do j = 1, jjm
143 do i = 1, iim
144 zmasse(j, l) = zmasse(j, l) + masseby(i, j, l)
145 v(j, l) = v(j, l) + flux_v_cum(i, j, l)
146 enddo
147 factv(j, l) = cv_2d(1, j) / zmasse(j, l)
148 enddo
149 enddo
150
151 ! Transport dans le plan latitude-altitude
152
153 vq = 0.
154 psiQ = 0.
155 do iQ = 1, nQ
156 vqtmp = 0.
157 do l = 1, llm
158 do j = 1, jjm
159 ! Calcul des moyennes zonales du transport total et de vqtmp
160 do i = 1, iim
161 vq(j, l, itot, iQ) = vq(j, l, itot, iQ) &
162 + flux_vQ_cum(i, j, l, iQ)
163 qy = 0.5 * (Q_cum(i, j, l, iQ) * masse_cum(i, j, l) &
164 + Q_cum(i, j + 1, l, iQ) * masse_cum(i, j + 1, l))
165 vqtmp(j, l) = vqtmp(j, l) + flux_v_cum(i, j, l) * qy &
166 / (0.5 * (masse_cum(i, j, l) + masse_cum(i, j + 1, l)))
167 vq(j, l, iave, iQ) = vq(j, l, iave, iQ) + qy
168 enddo
169 ! Decomposition
170 vq(j, l, iave, iQ) = vq(j, l, iave, iQ) / zmasse(j, l)
171 vq(j, l, itot, iQ) = vq(j, l, itot, iQ) * factv(j, l)
172 vqtmp(j, l) = vqtmp(j, l) * factv(j, l)
173 vq(j, l, immc, iQ) = v(j, l) * vq(j, l, iave, iQ) * factv(j, l)
174 vq(j, l, itrs, iQ) = vq(j, l, itot, iQ) - vqtmp(j, l)
175 vq(j, l, istn, iQ) = vqtmp(j, l) - vq(j, l, immc, iQ)
176 enddo
177 enddo
178 ! Fonction de courant méridienne pour la quantité Q
179 do l = llm, 1, -1
180 do j = 1, jjm
181 psiQ(j, l, iQ) = psiQ(j, l + 1, iQ) + vq(j, l, itot, iQ)
182 enddo
183 enddo
184 enddo
185
186 ! Fonction de courant pour la circulation méridienne moyenne
187 psi = 0.
188 do l = llm, 1, -1
189 do j = 1, jjm
190 psi(j, l) = psi(j, l + 1) + v(j, l)
191 v(j, l) = v(j, l) * factv(j, l)
192 enddo
193 enddo
194
195 ! Sorties proprement dites
196 do iQ = 1, nQ
197 do itr = 1, ntr
198 call histwrite(fileid, znom(itr, iQ), itau, vq(:, :, itr, iQ))
199 enddo
200 call histwrite(fileid, 'psi' // nom(iQ), itau, psiQ(:, :llm, iQ))
201 enddo
202
203 call histwrite(fileid, 'masse', itau, zmasse)
204 call histwrite(fileid, 'v', itau, v)
205 psi = psi * 1e-9
206 call histwrite(fileid, 'psi', itau, psi(:, :llm))
207
208 ! Intégrale verticale
209
210 forall (iQ = 1: nQ, itr = 2: ntr) avq(:, itr, iQ) &
211 = sum(vq(:, :, itr, iQ) * zmasse, dim=2) / cv_2d(1, :)
212
213 do iQ = 1, nQ
214 do itr = 2, ntr
215 call histwrite(fileid, 'a' // znom(itr, iQ), itau, avq(:, itr, iQ))
216 enddo
217 enddo
218
219 icum = 0
220 endif writing_step
221
222 end SUBROUTINE bilan_dyn
223
224 end module bilan_dyn_m

  ViewVC Help
Powered by ViewVC 1.1.21