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

Contents of /trunk/dyn3d/calfis.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 90 - (show annotations)
Wed Mar 12 21:16:36 2014 UTC (10 years, 2 months ago) by guez
File size: 8637 byte(s)
Removed procedures ini_histday, ini_histhf, write_histday and
write_histhf.

Divided file regr_pr_coefoz.f into regr_pr_av.f and
regr_pr_int.f. (Following LMDZ.) Divided module regr_pr_coefoz into
modules regr_pr_av_m and regr_pr_int_m. Renamed regr_pr_av_coefoz to
regr_pr_av and regr_pr_int_coefoz to regr_pr_int. The idea is that
those procedures are more general than Mobidic.

Removed argument dudyn of calfis and physiq. dudyn is not used either
in LMDZ. Removed computation in calfis of unused variable zpsrf (not
used either in LMDZ). Removed useless computation of dqfi in calfis
(part 62): the results were overwritten. (Same in LMDZ.)

1 module calfis_m
2
3 IMPLICIT NONE
4
5 contains
6
7 SUBROUTINE calfis(rdayvrai, time, ucov, vcov, teta, q, ps, pk, phis, phi, &
8 w, dufi, dvfi, dtetafi, dqfi, dpfi, lafin)
9
10 ! From dyn3d/calfis.F, version 1.3, 2005/05/25 13:10:09
11 ! Authors: P. Le Van, F. Hourdin
12
13 ! 1. R\'earrangement des tableaux et transformation des variables
14 ! dynamiques en variables physiques
15
16 ! 2. Calcul des termes physiques
17 ! 3. Retransformation des tendances physiques en tendances dynamiques
18
19 ! Remarques:
20
21 ! - Les vents sont donn\'es dans la physique par leurs composantes
22 ! naturelles.
23
24 ! - La variable thermodynamique de la physique est une variable
25 ! intensive : T.
26 ! Pour la dynamique on prend T * (preff / p(l))**kappa
27
28 ! - Les deux seules variables d\'ependant de la g\'eom\'etrie
29 ! n\'ecessaires pour la physique sont la latitude (pour le
30 ! rayonnement) et l'aire de la maille (quand on veut int\'egrer une
31 ! grandeur horizontalement).
32
33 use comconst, only: kappa, cpp, dtphys, g
34 use comgeom, only: apoln, cu_2d, cv_2d, unsaire_2d, apols, rlonu, rlonv
35 use dimens_m, only: iim, jjm, llm, nqmx
36 use dimphy, only: klon
37 use disvert_m, only: preff
38 use grid_change, only: dyn_phy, gr_fi_dyn
39 use iniadvtrac_m, only: niadv
40 use nr_util, only: pi
41 use physiq_m, only: physiq
42 use pressure_var, only: p3d, pls
43
44 REAL, intent(in):: rdayvrai
45 REAL, intent(in):: time ! heure de la journ\'ee en fraction de jour
46
47 REAL, intent(in):: ucov(iim + 1, jjm + 1, llm)
48 ! ucov covariant zonal velocity
49
50 REAL, intent(in):: vcov(iim + 1, jjm, llm)
51 ! vcov covariant meridional velocity
52
53 REAL, intent(in):: teta(iim + 1, jjm + 1, llm) ! teta potential temperature
54
55 REAL, intent(in):: q(iim + 1, jjm + 1, llm, nqmx)
56 ! mass fractions of advected fields
57
58 REAL, intent(in):: ps(iim + 1, jjm + 1) ! ps surface pressure
59
60 REAL, intent(in):: pk(iim + 1, jjm + 1, llm)
61 ! Exner = cp * (p / preff)**kappa
62
63 REAL, intent(in):: phis(iim + 1, jjm + 1)
64 REAL, intent(in):: phi(iim + 1, jjm + 1, llm)
65 REAL, intent(in):: w(iim + 1, jjm + 1, llm)
66
67 REAL, intent(out):: dufi(iim + 1, jjm + 1, llm)
68 ! tendency for the covariant zonal velocity (m2 s-2)
69
70 REAL, intent(out):: dvfi(iim + 1, jjm, llm)
71 ! tendency for the natural meridional velocity
72
73 REAL, intent(out):: dtetafi(iim + 1, jjm + 1, llm)
74 ! tendency for the potential temperature
75
76 REAL, intent(out):: dqfi(iim + 1, jjm + 1, llm, nqmx)
77 REAL, intent(out):: dpfi(iim + 1, jjm + 1) ! tendance sur la pression
78 LOGICAL, intent(in):: lafin
79
80 ! Local:
81
82 INTEGER i, j, l, ig0, iq, iiq
83 REAL zpsrf(klon)
84
85 REAL paprs(klon, llm+1), play(klon, llm)
86 ! paprs defini aux (llm +1) interfaces des couches
87 ! play defini aux (llm) milieux des couches
88
89 REAL pphi(klon, llm), pphis(klon)
90
91 REAL u(klon, llm), v(klon, llm)
92 real zvfi(iim + 1, jjm + 1, llm)
93 REAL t(klon, llm) ! temperature
94 real qx(klon, llm, nqmx) ! mass fractions of advected fields
95 REAL omega(klon, llm)
96
97 REAL d_u(klon, llm), d_v(klon, llm) ! tendances physiques du vent (m s-2)
98 REAL d_t(klon, llm), d_qx(klon, llm, nqmx)
99 REAL d_ps(klon)
100
101 REAL z1(iim)
102 REAL pksurcp(iim + 1, jjm + 1)
103
104 !-----------------------------------------------------------------------
105
106 !!print *, "Call sequence information: calfis"
107
108 ! 40. transformation des variables dynamiques en variables physiques:
109
110 ! 42. pression intercouches :
111
112 forall (l = 1: llm+1) paprs(:, l) = pack(p3d(:, :, l), dyn_phy)
113
114 ! 43. temperature naturelle (en K) et pressions milieux couches
115 DO l=1, llm
116 pksurcp = pk(:, :, l) / cpp
117 pls(:, :, l) = preff * pksurcp**(1./ kappa)
118 play(:, l) = pack(pls(:, :, l), dyn_phy)
119 t(:, l) = pack(teta(:, :, l) * pksurcp, dyn_phy)
120 ENDDO
121
122 ! 43.bis traceurs
123 DO iq=1, nqmx
124 iiq=niadv(iq)
125 DO l=1, llm
126 qx(1, l, iq) = q(1, 1, l, iiq)
127 ig0 = 2
128 DO j=2, jjm
129 DO i = 1, iim
130 qx(ig0, l, iq) = q(i, j, l, iiq)
131 ig0 = ig0 + 1
132 ENDDO
133 ENDDO
134 qx(ig0, l, iq) = q(1, jjm + 1, l, iiq)
135 ENDDO
136 ENDDO
137
138 ! Geopotentiel calcule par rapport a la surface locale:
139 forall (l = 1:llm) pphi(:, l) = pack(phi(:, :, l), dyn_phy)
140 pphis = pack(phis, dyn_phy)
141 forall (l = 1:llm) pphi(:, l)=pphi(:, l) - pphis
142
143 ! Calcul de la vitesse verticale (en Pa*m*s ou Kg/s)
144 DO l=1, llm
145 omega(1, l)=w(1, 1, l) * g /apoln
146 ig0=2
147 DO j=2, jjm
148 DO i = 1, iim
149 omega(ig0, l) = w(i, j, l) * g * unsaire_2d(i, j)
150 ig0 = ig0 + 1
151 ENDDO
152 ENDDO
153 omega(ig0, l)=w(1, jjm + 1, l) * g /apols
154 ENDDO
155
156 ! 45. champ u:
157
158 DO l=1, llm
159 DO j=2, jjm
160 ig0 = 1+(j-2)*iim
161 u(ig0+1, l)= 0.5 &
162 * (ucov(iim, j, l) / cu_2d(iim, j) + ucov(1, j, l) / cu_2d(1, j))
163 DO i=2, iim
164 u(ig0+i, l)= 0.5 * (ucov(i-1, j, l)/cu_2d(i-1, j) &
165 + ucov(i, j, l)/cu_2d(i, j))
166 end DO
167 end DO
168 end DO
169
170 ! 46.champ v:
171
172 forall (j = 2: jjm, l = 1: llm) zvfi(:iim, j, l)= 0.5 &
173 * (vcov(:iim, j-1, l) / cv_2d(:iim, j-1) &
174 + vcov(:iim, j, l) / cv_2d(:iim, j))
175 zvfi(iim + 1, 2:jjm, :) = zvfi(1, 2:jjm, :)
176
177 ! 47. champs de vents au p\^ole nord
178 ! U = 1 / pi * integrale [ v * cos(long) * d long ]
179 ! V = 1 / pi * integrale [ v * sin(long) * d long ]
180
181 DO l=1, llm
182 z1(1) =(rlonu(1)-rlonu(iim)+2.*pi)*vcov(1, 1, l)/cv_2d(1, 1)
183 DO i=2, iim
184 z1(i) =(rlonu(i)-rlonu(i-1))*vcov(i, 1, l)/cv_2d(i, 1)
185 ENDDO
186
187 u(1, l) = SUM(COS(rlonv(:iim)) * z1) / pi
188 zvfi(:, 1, l) = SUM(SIN(rlonv(:iim)) * z1) / pi
189 ENDDO
190
191 ! 48. champs de vents au p\^ole sud:
192 ! U = 1 / pi * integrale [ v * cos(long) * d long ]
193 ! V = 1 / pi * integrale [ v * sin(long) * d long ]
194
195 DO l=1, llm
196 z1(1) =(rlonu(1)-rlonu(iim)+2.*pi)*vcov(1, jjm, l) &
197 /cv_2d(1, jjm)
198 DO i=2, iim
199 z1(i) =(rlonu(i)-rlonu(i-1))*vcov(i, jjm, l)/cv_2d(i, jjm)
200 ENDDO
201
202 u(klon, l) = SUM(COS(rlonv(:iim)) * z1) / pi
203 zvfi(:, jjm + 1, l) = SUM(SIN(rlonv(:iim)) * z1) / pi
204 ENDDO
205
206 forall(l= 1: llm) v(:, l) = pack(zvfi(:, :, l), dyn_phy)
207
208 ! Appel de la physique :
209 CALL physiq(lafin, rdayvrai, time, dtphys, paprs, play, pphi, pphis, u, &
210 v, t, qx, omega, d_u, d_v, d_t, d_qx, d_ps)
211
212 ! transformation des tendances physiques en tendances dynamiques:
213
214 dpfi = gr_fi_dyn(d_ps)
215
216 ! 62. enthalpie potentielle
217 do l=1, llm
218 dtetafi(:, :, l) = cpp * gr_fi_dyn(d_t(:, l)) / pk(:, :, l)
219 end do
220
221 ! 63. traceurs
222
223 ! initialisation des tendances
224 dqfi=0.
225
226 DO iq=1, nqmx
227 iiq=niadv(iq)
228 DO l=1, llm
229 DO i=1, iim + 1
230 dqfi(i, 1, l, iiq) = d_qx(1, l, iq)
231 dqfi(i, jjm + 1, l, iiq) = d_qx(klon, l, iq)
232 ENDDO
233 DO j=2, jjm
234 ig0=1+(j-2)*iim
235 DO i=1, iim
236 dqfi(i, j, l, iiq) = d_qx(ig0+i, l, iq)
237 ENDDO
238 dqfi(iim + 1, j, l, iiq) = dqfi(1, j, l, iq)
239 ENDDO
240 ENDDO
241 ENDDO
242
243 ! 65. champ u:
244
245 DO l=1, llm
246 DO i=1, iim + 1
247 dufi(i, 1, l) = 0.
248 dufi(i, jjm + 1, l) = 0.
249 ENDDO
250
251 DO j=2, jjm
252 ig0=1+(j-2)*iim
253 DO i=1, iim-1
254 dufi(i, j, l)= 0.5*(d_u(ig0+i, l)+d_u(ig0+i+1, l))*cu_2d(i, j)
255 ENDDO
256 dufi(iim, j, l)= 0.5*(d_u(ig0+1, l)+d_u(ig0+iim, l))*cu_2d(iim, j)
257 dufi(iim + 1, j, l)=dufi(1, j, l)
258 ENDDO
259 ENDDO
260
261 ! 67. champ v:
262
263 DO l=1, llm
264 DO j=2, jjm-1
265 ig0=1+(j-2)*iim
266 DO i=1, iim
267 dvfi(i, j, l)= 0.5*(d_v(ig0+i, l)+d_v(ig0+i+iim, l))*cv_2d(i, j)
268 ENDDO
269 dvfi(iim + 1, j, l) = dvfi(1, j, l)
270 ENDDO
271 ENDDO
272
273 ! 68. champ v pr\`es des p\^oles:
274 ! v = U * cos(long) + V * SIN(long)
275
276 DO l=1, llm
277 DO i=1, iim
278 dvfi(i, 1, l)= d_u(1, l)*COS(rlonv(i))+d_v(1, l)*SIN(rlonv(i))
279 dvfi(i, jjm, l)=d_u(klon, l)*COS(rlonv(i)) +d_v(klon, l)*SIN(rlonv(i))
280 dvfi(i, 1, l)= 0.5*(dvfi(i, 1, l)+d_v(i+1, l))*cv_2d(i, 1)
281 dvfi(i, jjm, l)= 0.5 &
282 * (dvfi(i, jjm, l) + d_v(klon - iim - 1 + i, l)) * cv_2d(i, jjm)
283 ENDDO
284
285 dvfi(iim + 1, 1, l) = dvfi(1, 1, l)
286 dvfi(iim + 1, jjm, l)= dvfi(1, jjm, l)
287 ENDDO
288
289 END SUBROUTINE calfis
290
291 end module calfis_m

  ViewVC Help
Powered by ViewVC 1.1.21