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

Contents of /trunk/dyn3d/calfis.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 154 - (show annotations)
Tue Jul 7 17:49:23 2015 UTC (8 years, 10 months ago) by guez
Original Path: trunk/Sources/dyn3d/calfis.f
File size: 8426 byte(s)
Removed argument dtphys of physiq. Use it directly from comconst in
physiq instead.

Donwgraded variables eignfnu, eignfnv of module inifgn_m to dummy
arguments of SUBROUTINE inifgn. They were not used elsewhere than in
the calling procedure inifilr. Renamed argument dv of inifgn to eignval_v.

Made alboc and alboc_cd independent of the size of arguments. Now we
can call them only at indices knindex in interfsurf_hq, where we need
them. Fixed a bug in alboc_cd: rmu0 was modified, and the
corresponding actual argument in interfsurf_hq is an intent(in)
argument of interfsurf_hq.

Variables of size knon instead of klon in interfsur_lim and interfsurf_hq.

Removed argument alb_new of interfsurf_hq because it was the same than
alblw. Simplified test on cycle_diurne, following LMDZ.

Moved tests on nbapp_rad from physiq to read_clesphys2. No need for
separate counter itaprad, we can use itap. Define lmt_pas and radpas
from integer input parameters instead of real-type computed values.

1 module calfis_m
2
3 IMPLICIT NONE
4
5 contains
6
7 SUBROUTINE calfis(ucov, vcov, teta, q, pk, phis, phi, w, dufi, dvfi, &
8 dtetafi, dqfi, dayvrai, time, 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 tendances 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)**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, g
34 use comgeom, only: apoln, cu_2d, cv_2d, unsaire_2d, apols
35 use dimens_m, only: iim, jjm, llm, nqmx
36 use dimphy, only: klon
37 use disvert_m, only: preff
38 use dynetat0_m, only: rlonu, rlonv
39 use grid_change, only: dyn_phy, gr_fi_dyn
40 use nr_util, only: pi
41 use physiq_m, only: physiq
42 use pressure_var, only: p3d, pls
43
44 REAL, intent(in):: ucov(:, :, :) ! (iim + 1, jjm + 1, llm)
45 ! covariant zonal velocity
46
47 REAL, intent(in):: vcov(:, :, :) ! (iim + 1, jjm, llm)
48 !covariant meridional velocity
49
50 REAL, intent(in):: teta(:, :, :) ! (iim + 1, jjm + 1, llm)
51 ! potential temperature
52
53 REAL, intent(in):: q(:, :, :, :) ! (iim + 1, jjm + 1, llm, nqmx)
54 ! mass fractions of advected fields
55
56 REAL, intent(in):: pk(:, :, :) ! (iim + 1, jjm + 1, llm)
57 ! Exner = cp * (p / preff)**kappa
58
59 REAL, intent(in):: phis(:, :) ! (iim + 1, jjm + 1)
60 REAL, intent(in):: phi(:, :, :) ! (iim + 1, jjm + 1, llm)
61 REAL, intent(in):: w(:, :, :) ! (iim + 1, jjm + 1, llm) in kg / s
62
63 REAL, intent(out):: dufi(:, :, :) ! (iim + 1, jjm + 1, llm)
64 ! tendency for the covariant zonal velocity (m2 s-2)
65
66 REAL, intent(out):: dvfi(:, :, :) ! (iim + 1, jjm, llm)
67 ! tendency for the natural meridional velocity
68
69 REAL, intent(out):: dtetafi(:, :, :) ! (iim + 1, jjm + 1, llm)
70 ! tendency for the potential temperature
71
72 REAL, intent(out):: dqfi(:, :, :, :) ! (iim + 1, jjm + 1, llm, nqmx)
73
74 integer, intent(in):: dayvrai
75 ! current day number, based at value 1 on January 1st of annee_ref
76
77 REAL, intent(in):: time ! time of day, as a fraction of day length
78 LOGICAL, intent(in):: lafin
79
80 ! Local:
81 INTEGER i, j, l, ig0, iq
82 REAL paprs(klon, llm + 1) ! aux interfaces des couches
83 REAL play(klon, llm) ! aux milieux des couches
84 REAL pphi(klon, llm), pphis(klon)
85 REAL u(klon, llm), v(klon, llm)
86 real zvfi(iim + 1, jjm + 1, llm)
87 REAL t(klon, llm) ! temperature, in K
88 real qx(klon, llm, nqmx) ! mass fractions of advected fields
89 REAL omega(klon, llm)
90 REAL d_u(klon, llm), d_v(klon, llm) ! tendances physiques du vent (m s-2)
91 REAL d_t(klon, llm), d_qx(klon, llm, nqmx)
92 REAL z1(iim)
93 REAL pksurcp(iim + 1, jjm + 1)
94
95 !-----------------------------------------------------------------------
96
97 !!print *, "Call sequence information: calfis"
98
99 ! 40. Transformation des variables dynamiques en variables physiques :
100
101 ! 42. Pression intercouches :
102 forall (l = 1: llm + 1) paprs(:, l) = pack(p3d(:, :, l), dyn_phy)
103
104 ! 43. Température et pression milieu couche
105 DO l = 1, llm
106 pksurcp = pk(:, :, l) / cpp
107 pls(:, :, l) = preff * pksurcp**(1./ kappa)
108 play(:, l) = pack(pls(:, :, l), dyn_phy)
109 t(:, l) = pack(teta(:, :, l) * pksurcp, dyn_phy)
110 ENDDO
111
112 ! 43.bis Traceurs :
113 forall (iq = 1: nqmx, l = 1: llm) &
114 qx(:, l, iq) = pack(q(:, :, l, iq), dyn_phy)
115
116 ! Geopotentiel calcule par rapport a la surface locale :
117 forall (l = 1 :llm) pphi(:, l) = pack(phi(:, :, l), dyn_phy)
118 pphis = pack(phis, dyn_phy)
119 forall (l = 1: llm) pphi(:, l) = pphi(:, l) - pphis
120
121 ! Calcul de la vitesse verticale :
122 forall (l = 1: llm)
123 omega(1, l) = w(1, 1, l) * g / apoln
124 omega(2: klon - 1, l) &
125 = pack(w(:iim, 2: jjm, l) * g * unsaire_2d(:iim, 2: jjm), .true.)
126 omega(klon, l) = w(1, jjm + 1, l) * g / apols
127 END forall
128
129 ! 45. champ u:
130
131 DO l = 1, llm
132 DO j = 2, jjm
133 ig0 = 1 + (j - 2) * iim
134 u(ig0 + 1, l) = 0.5 &
135 * (ucov(iim, j, l) / cu_2d(iim, j) + ucov(1, j, l) / cu_2d(1, j))
136 DO i = 2, iim
137 u(ig0 + i, l) = 0.5 * (ucov(i - 1, j, l) / cu_2d(i - 1, j) &
138 + ucov(i, j, l) / cu_2d(i, j))
139 end DO
140 end DO
141 end DO
142
143 ! 46.champ v:
144
145 forall (j = 2: jjm, l = 1: llm) zvfi(:iim, j, l) = 0.5 &
146 * (vcov(:iim, j - 1, l) / cv_2d(:iim, j - 1) &
147 + vcov(:iim, j, l) / cv_2d(:iim, j))
148 zvfi(iim + 1, 2:jjm, :) = zvfi(1, 2:jjm, :)
149
150 ! 47. champs de vents au p\^ole nord
151 ! U = 1 / pi * integrale [ v * cos(long) * d long ]
152 ! V = 1 / pi * integrale [ v * sin(long) * d long ]
153
154 DO l = 1, llm
155 z1(1) = (rlonu(1) - rlonu(iim) + 2. * pi) * vcov(1, 1, l) / cv_2d(1, 1)
156 DO i = 2, iim
157 z1(i) = (rlonu(i) - rlonu(i - 1)) * vcov(i, 1, l) / cv_2d(i, 1)
158 ENDDO
159
160 u(1, l) = SUM(COS(rlonv(:iim)) * z1) / pi
161 zvfi(:, 1, l) = SUM(SIN(rlonv(:iim)) * z1) / pi
162 ENDDO
163
164 ! 48. champs de vents au p\^ole sud:
165 ! U = 1 / pi * integrale [ v * cos(long) * d long ]
166 ! V = 1 / pi * integrale [ v * sin(long) * d long ]
167
168 DO l = 1, llm
169 z1(1) = (rlonu(1) - rlonu(iim) + 2. * pi) * vcov(1, jjm, l) &
170 /cv_2d(1, jjm)
171 DO i = 2, iim
172 z1(i) = (rlonu(i) - rlonu(i - 1)) * vcov(i, jjm, l) / cv_2d(i, jjm)
173 ENDDO
174
175 u(klon, l) = SUM(COS(rlonv(:iim)) * z1) / pi
176 zvfi(:, jjm + 1, l) = SUM(SIN(rlonv(:iim)) * z1) / pi
177 ENDDO
178
179 forall(l = 1: llm) v(:, l) = pack(zvfi(:, :, l), dyn_phy)
180
181 ! Appel de la physique :
182 CALL physiq(lafin, dayvrai, time, paprs, play, pphi, pphis, u, v, t, qx, &
183 omega, d_u, d_v, d_t, d_qx)
184
185 ! transformation des tendances physiques en tendances dynamiques:
186
187 ! 62. enthalpie potentielle
188 do l = 1, llm
189 dtetafi(:, :, l) = cpp * gr_fi_dyn(d_t(:, l)) / pk(:, :, l)
190 end do
191
192 ! 63. traceurs
193 DO iq = 1, nqmx
194 DO l = 1, llm
195 DO i = 1, iim + 1
196 dqfi(i, 1, l, iq) = d_qx(1, l, iq)
197 dqfi(i, jjm + 1, l, iq) = d_qx(klon, l, iq)
198 ENDDO
199 DO j = 2, jjm
200 ig0 = 1 + (j - 2) * iim
201 DO i = 1, iim
202 dqfi(i, j, l, iq) = d_qx(ig0 + i, l, iq)
203 ENDDO
204 dqfi(iim + 1, j, l, iq) = dqfi(1, j, l, iq)
205 ENDDO
206 ENDDO
207 ENDDO
208
209 ! 65. champ u:
210 DO l = 1, llm
211 DO i = 1, iim + 1
212 dufi(i, 1, l) = 0.
213 dufi(i, jjm + 1, l) = 0.
214 ENDDO
215
216 DO j = 2, jjm
217 ig0 = 1 + (j - 2) * iim
218 DO i = 1, iim - 1
219 dufi(i, j, l) = 0.5 * (d_u(ig0 + i, l) + d_u(ig0 + i+1, l)) &
220 * cu_2d(i, j)
221 ENDDO
222 dufi(iim, j, l) = 0.5 * (d_u(ig0 + 1, l) + d_u(ig0 + iim, l)) &
223 * cu_2d(iim, j)
224 dufi(iim + 1, j, l) = dufi(1, j, l)
225 ENDDO
226 ENDDO
227
228 ! 67. champ v:
229
230 DO l = 1, llm
231 DO j = 2, jjm - 1
232 ig0 = 1 + (j - 2) * iim
233 DO i = 1, iim
234 dvfi(i, j, l) = 0.5 * (d_v(ig0 + i, l) + d_v(ig0 + i+iim, l)) &
235 * cv_2d(i, j)
236 ENDDO
237 dvfi(iim + 1, j, l) = dvfi(1, j, l)
238 ENDDO
239 ENDDO
240
241 ! 68. champ v pr\`es des p\^oles:
242 ! v = U * cos(long) + V * SIN(long)
243
244 DO l = 1, llm
245 DO i = 1, iim
246 dvfi(i, 1, l) = d_u(1, l) * COS(rlonv(i)) + d_v(1, l) * SIN(rlonv(i))
247 dvfi(i, jjm, l) = d_u(klon, l) * COS(rlonv(i)) &
248 + d_v(klon, l) * SIN(rlonv(i))
249 dvfi(i, 1, l) = 0.5 * (dvfi(i, 1, l) + d_v(i + 1, l)) * cv_2d(i, 1)
250 dvfi(i, jjm, l) = 0.5 &
251 * (dvfi(i, jjm, l) + d_v(klon - iim - 1 + i, l)) * cv_2d(i, jjm)
252 ENDDO
253
254 dvfi(iim + 1, 1, l) = dvfi(1, 1, l)
255 dvfi(iim + 1, jjm, l) = dvfi(1, jjm, l)
256 ENDDO
257
258 END SUBROUTINE calfis
259
260 end module calfis_m

  ViewVC Help
Powered by ViewVC 1.1.21