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

Contents of /trunk/dyn3d/calfis.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 339 - (show annotations)
Thu Sep 26 17:08:42 2019 UTC (4 years, 8 months ago) by guez
File size: 8569 byte(s)
Simplify newmicro and rename dummy arguments

Rename dummy argument ucov of procedure advect to ang_3d. Rename dummy
argument radliq of procedure fisrtilp to cldliq. Rename dummy argument
qlwp of procedure newmicro to cldliq. Motivation: same name across
procedures.

Remove useless intermediary local variable rel in procedure
newmicro. The value of rad_chaud can be used instead of 1 in the
computation of cldtau if zflwp is 0: it does not matter.

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

  ViewVC Help
Powered by ViewVC 1.1.21