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

Contents of /trunk/dyn3d/calfis.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 130 - (show annotations)
Tue Feb 24 15:43:51 2015 UTC (9 years, 3 months ago) by guez
File size: 8417 byte(s)
The information in argument rdayvrai of calfis was redundant with the
information in argument time. Furthermore, in the physics part of gcm,
we need separately the day number (an integer) and the time of
day. So, replaced real argument rdayvrai of calfis containing elapsed
time by integer argument dayvrai containing day number. Corresponding
change in leapfrog. In procedure physiq, replaced real argument
rdayvrai by integer argument dayvrai. In procedures readsulfate and
readsulfate_preind, replaced real argument r_day by arguments dayvrai
and time.

In procedure alboc, replaced real argument rjour by integer argument
jour. alboc was always called by interfsurf_hq with actual argument
real(jour), and the meaning of the dummy argument in alboc seems to be
that it should be an integer.

In procedure leapfrog, local variable time could not be > 1. Removed
test.

In physiq, replaced nint(rdayvrai) by dayvrai. This changes the
results since julien now changes at 0 h instead of 12 h. This follows
LMDZ, where the argument of ozonecm is days_elapsed+1.

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

  ViewVC Help
Powered by ViewVC 1.1.21