/[lmdze]/trunk/Sources/dyn3d/leapfrog.f
ViewVC logotype

Contents of /trunk/Sources/dyn3d/leapfrog.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 96 - (show annotations)
Fri Apr 4 11:30:34 2014 UTC (10 years, 1 month ago) by guez
Original Path: trunk/dyn3d/leapfrog.f
File size: 8731 byte(s)
In procedure leapfrog, computation of p3d and a call to exner_hyb were
made before and after the call to calfis. This was a repetition of the
same calculation since calfis does not change the surface
pressure. Kept only one calculation, and moved it before the test for
the call to calfis.

1 module leapfrog_m
2
3 IMPLICIT NONE
4
5 contains
6
7 SUBROUTINE leapfrog(ucov, vcov, teta, ps, masse, phis, q, time_0)
8
9 ! From dyn3d/leapfrog.F, version 1.6, 2005/04/13 08:58:34 revision 616
10 ! Authors: P. Le Van, L. Fairhead, F. Hourdin
11 ! Matsuno-leapfrog scheme.
12
13 use addfi_m, only: addfi
14 use bilan_dyn_m, only: bilan_dyn
15 use caladvtrac_m, only: caladvtrac
16 use caldyn_m, only: caldyn
17 USE calfis_m, ONLY: calfis
18 USE comconst, ONLY: daysec, dtphys, dtvr
19 USE comgeom, ONLY: aire_2d, apoln, apols
20 USE disvert_m, ONLY: ap, bp
21 USE conf_gcm_m, ONLY: day_step, iconser, iperiod, iphysiq, nday, offline, &
22 iflag_phys, ok_guide, iecri
23 USE dimens_m, ONLY: iim, jjm, llm, nqmx
24 use dissip_m, only: dissip
25 USE dynetat0_m, ONLY: day_ini
26 use dynredem1_m, only: dynredem1
27 USE exner_hyb_m, ONLY: exner_hyb
28 use filtreg_m, only: filtreg
29 use fluxstokenc_m, only: fluxstokenc
30 use geopot_m, only: geopot
31 USE guide_m, ONLY: guide
32 use inidissip_m, only: idissip
33 use integrd_m, only: integrd
34 use nr_util, only: assert
35 USE pressure_var, ONLY: p3d
36 USE temps, ONLY: itau_dyn
37 use writedynav_m, only: writedynav
38 use writehist_m, only: writehist
39
40 ! Variables dynamiques:
41 REAL, intent(inout):: ucov(:, :, :) ! (iim + 1, jjm + 1, llm) vent covariant
42 REAL, intent(inout):: vcov(:, :, :) ! (iim + 1, jjm, llm) ! vent covariant
43
44 REAL, intent(inout):: teta(:, :, :) ! (iim + 1, jjm + 1, llm)
45 ! potential temperature
46
47 REAL, intent(inout):: ps(:, :) ! (iim + 1, jjm + 1) pression au sol, en Pa
48 REAL, intent(inout):: masse(:, :, :) ! (iim + 1, jjm + 1, llm) masse d'air
49 REAL, intent(in):: phis(:, :) ! (iim + 1, jjm + 1) surface geopotential
50
51 REAL, intent(inout):: q(:, :, :, :) ! (iim + 1, jjm + 1, llm, nqmx)
52 ! mass fractions of advected fields
53
54 REAL, intent(in):: time_0
55
56 ! Local:
57
58 ! Variables dynamiques:
59
60 REAL pks(iim + 1, jjm + 1) ! exner au sol
61 REAL pk(iim + 1, jjm + 1, llm) ! exner au milieu des couches
62 REAL pkf(iim + 1, jjm + 1, llm) ! exner filtr\'e au milieu des couches
63 REAL phi(iim + 1, jjm + 1, llm) ! geopotential
64 REAL w(iim + 1, jjm + 1, llm) ! vitesse verticale
65
66 ! Variables dynamiques intermediaire pour le transport
67 ! Flux de masse :
68 REAL pbaru(iim + 1, jjm + 1, llm), pbarv(iim + 1, jjm, llm)
69
70 ! Variables dynamiques au pas - 1
71 REAL vcovm1(iim + 1, jjm, llm), ucovm1(iim + 1, jjm + 1, llm)
72 REAL tetam1(iim + 1, jjm + 1, llm), psm1(iim + 1, jjm + 1)
73 REAL massem1(iim + 1, jjm + 1, llm)
74
75 ! Tendances dynamiques
76 REAL dv((iim + 1) * jjm, llm), dudyn(iim + 1, jjm + 1, llm)
77 REAL dteta(iim + 1, jjm + 1, llm)
78 real dp((iim + 1) * (jjm + 1))
79
80 ! Tendances de la dissipation :
81 REAL dvdis(iim + 1, jjm, llm), dudis(iim + 1, jjm + 1, llm)
82 REAL dtetadis(iim + 1, jjm + 1, llm)
83
84 ! Tendances physiques
85 REAL dvfi(iim + 1, jjm, llm), dufi(iim + 1, jjm + 1, llm)
86 REAL dtetafi(iim + 1, jjm + 1, llm), dqfi(iim + 1, jjm + 1, llm, nqmx)
87
88 ! Variables pour le fichier histoire
89
90 INTEGER itau ! index of the time step of the dynamics, starts at 0
91 INTEGER itaufin
92 REAL time ! time of day, as a fraction of day length
93 real finvmaold(iim + 1, jjm + 1, llm)
94 INTEGER l
95 REAL rdayvrai, rdaym_ini
96
97 ! Variables test conservation \'energie
98 REAL ecin(iim + 1, jjm + 1, llm), ecin0(iim + 1, jjm + 1, llm)
99
100 REAL vcont((iim + 1) * jjm, llm), ucont((iim + 1) * (jjm + 1), llm)
101 logical leapf
102 real dt ! time step, in s
103
104 !---------------------------------------------------
105
106 print *, "Call sequence information: leapfrog"
107 call assert(shape(ucov) == (/iim + 1, jjm + 1, llm/), "leapfrog")
108
109 itaufin = nday * day_step
110 ! "day_step" is a multiple of "iperiod", therefore so is "itaufin".
111
112 ! On initialise la pression et la fonction d'Exner :
113 forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps
114 CALL exner_hyb(ps, p3d, pks, pk, pkf)
115
116 time_integration: do itau = 0, itaufin - 1
117 leapf = mod(itau, iperiod) /= 0
118 if (leapf) then
119 dt = 2 * dtvr
120 else
121 ! Matsuno
122 dt = dtvr
123 if (ok_guide .and. (itaufin - itau - 1) * dtvr > 21600.) &
124 call guide(itau, ucov, vcov, teta, q, masse, ps)
125 vcovm1 = vcov
126 ucovm1 = ucov
127 tetam1 = teta
128 massem1 = masse
129 psm1 = ps
130 finvmaold = masse
131 CALL filtreg(finvmaold, jjm + 1, llm, - 2, 2, .TRUE.)
132 end if
133
134 ! Calcul des tendances dynamiques:
135 CALL geopot(teta, pk, pks, phis, phi)
136 CALL caldyn(itau, ucov, vcov, teta, ps, masse, pk, pkf, phis, phi, &
137 dudyn, dv, dteta, dp, w, pbaru, pbarv, time_0, &
138 conser = MOD(itau, iconser) == 0)
139
140 CALL caladvtrac(q, pbaru, pbarv, p3d, masse, teta, pk)
141
142 ! Stokage du flux de masse pour traceurs offline:
143 IF (offline) CALL fluxstokenc(pbaru, pbarv, masse, teta, phi, phis, &
144 dtvr, itau)
145
146 ! Int\'egrations dynamique et traceurs:
147 CALL integrd(vcovm1, ucovm1, tetam1, psm1, massem1, dv, dudyn, dteta, &
148 dp, vcov, ucov, teta, q(:, :, :, :2), ps, masse, finvmaold, dt, &
149 leapf)
150
151 if (.not. leapf) then
152 ! Matsuno backward
153 forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps
154 CALL exner_hyb(ps, p3d, pks, pk, pkf)
155
156 ! Calcul des tendances dynamiques:
157 CALL geopot(teta, pk, pks, phis, phi)
158 CALL caldyn(itau + 1, ucov, vcov, teta, ps, masse, pk, pkf, phis, &
159 phi, dudyn, dv, dteta, dp, w, pbaru, pbarv, time_0, &
160 conser = .false.)
161
162 ! integrations dynamique et traceurs:
163 CALL integrd(vcovm1, ucovm1, tetam1, psm1, massem1, dv, dudyn, &
164 dteta, dp, vcov, ucov, teta, q(:, :, :, :2), ps, masse, &
165 finvmaold, dtvr, leapf=.false.)
166 end if
167
168 forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps
169 CALL exner_hyb(ps, p3d, pks, pk, pkf)
170
171 IF (MOD(itau + 1, iphysiq) == 0 .AND. iflag_phys /= 0) THEN
172 ! Calcul des tendances physiques:
173
174 rdaym_ini = itau * dtvr / daysec
175 rdayvrai = rdaym_ini + day_ini
176 time = REAL(mod(itau, day_step)) / day_step + time_0
177 IF (time > 1.) time = time - 1.
178
179 CALL calfis(rdayvrai, time, ucov, vcov, teta, q, pk, phis, phi, w, &
180 dufi, dvfi, dtetafi, dqfi, lafin = itau + 1 == itaufin)
181
182 ! Ajout des tendances physiques:
183 CALL addfi(ucov, vcov, teta, q, dufi, dvfi, dtetafi, dqfi)
184 ENDIF
185
186 IF (MOD(itau + 1, idissip) == 0) THEN
187 ! Dissipation horizontale et verticale des petites \'echelles
188
189 ! calcul de l'\'energie cin\'etique avant dissipation
190 call covcont(llm, ucov, vcov, ucont, vcont)
191 call enercin(vcov, ucov, vcont, ucont, ecin0)
192
193 ! dissipation
194 CALL dissip(vcov, ucov, teta, p3d, dvdis, dudis, dtetadis)
195 ucov = ucov + dudis
196 vcov = vcov + dvdis
197
198 ! On ajoute la tendance due \`a la transformation \'energie
199 ! cin\'etique en \'energie thermique par la dissipation
200 call covcont(llm, ucov, vcov, ucont, vcont)
201 call enercin(vcov, ucov, vcont, ucont, ecin)
202 dtetadis = dtetadis + (ecin0 - ecin) / pk
203 teta = teta + dtetadis
204
205 ! Calcul de la valeur moyenne aux p\^oles :
206 forall (l = 1: llm)
207 teta(:, 1, l) = SUM(aire_2d(:iim, 1) * teta(:iim, 1, l)) &
208 / apoln
209 teta(:, jjm + 1, l) = SUM(aire_2d(:iim, jjm+1) &
210 * teta(:iim, jjm + 1, l)) / apols
211 END forall
212 END IF
213
214 IF (MOD(itau + 1, iperiod) == 0) THEN
215 ! \'Ecriture du fichier histoire moyenne:
216 CALL writedynav(vcov, ucov, teta, pk, phi, q, masse, ps, phis, &
217 time = itau + 1)
218 call bilan_dyn(ps, masse, pk, pbaru, pbarv, teta, phi, ucov, vcov, &
219 q(:, :, :, 1))
220 ENDIF
221
222 IF (MOD(itau + 1, iecri * day_step) == 0) THEN
223 CALL geopot(teta, pk, pks, phis, phi)
224 CALL writehist(itau, vcov, ucov, teta, phi, q, masse, ps)
225 END IF
226 end do time_integration
227
228 CALL dynredem1("restart.nc", vcov, ucov, teta, q, masse, ps, &
229 itau = itau_dyn + itaufin)
230
231 ! Calcul des tendances dynamiques:
232 CALL geopot(teta, pk, pks, phis, phi)
233 CALL caldyn(itaufin, ucov, vcov, teta, ps, masse, pk, pkf, phis, phi, &
234 dudyn, dv, dteta, dp, w, pbaru, pbarv, time_0, &
235 conser = MOD(itaufin, iconser) == 0)
236
237 END SUBROUTINE leapfrog
238
239 end module leapfrog_m

  ViewVC Help
Powered by ViewVC 1.1.21