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

Contents of /trunk/dyn3d/leapfrog.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 130 - (show annotations)
Tue Feb 24 15:43:51 2015 UTC (9 years, 2 months ago) by guez
File size: 8380 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 leapfrog_m
2
3 IMPLICIT NONE
4
5 contains
6
7 SUBROUTINE leapfrog(ucov, vcov, teta, ps, masse, phis, q)
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
12 ! Intégration temporelle du modèle : Matsuno-leapfrog scheme.
13
14 use addfi_m, only: addfi
15 use bilan_dyn_m, only: bilan_dyn
16 use caladvtrac_m, only: caladvtrac
17 use caldyn_m, only: caldyn
18 USE calfis_m, ONLY: calfis
19 USE comconst, ONLY: daysec, dtvr
20 USE comgeom, ONLY: aire_2d, apoln, apols
21 USE disvert_m, ONLY: ap, bp
22 USE conf_gcm_m, ONLY: day_step, iconser, iperiod, iphysiq, nday, offline, &
23 iflag_phys, iecri
24 USE conf_guide_m, ONLY: ok_guide
25 USE dimens_m, ONLY: iim, jjm, llm, nqmx
26 use dissip_m, only: dissip
27 USE dynetat0_m, ONLY: day_ini
28 use dynredem1_m, only: dynredem1
29 USE exner_hyb_m, ONLY: exner_hyb
30 use filtreg_m, only: filtreg
31 use fluxstokenc_m, only: fluxstokenc
32 use geopot_m, only: geopot
33 USE guide_m, ONLY: guide
34 use inidissip_m, only: idissip
35 use integrd_m, only: integrd
36 use nr_util, only: assert
37 USE pressure_var, ONLY: p3d
38 USE temps, ONLY: itau_dyn
39 use writedynav_m, only: writedynav
40 use writehist_m, only: writehist
41
42 ! Variables dynamiques:
43 REAL, intent(inout):: ucov(:, :, :) ! (iim + 1, jjm + 1, llm) vent covariant
44 REAL, intent(inout):: vcov(:, :, :) ! (iim + 1, jjm, llm) ! vent covariant
45
46 REAL, intent(inout):: teta(:, :, :) ! (iim + 1, jjm + 1, llm)
47 ! potential temperature
48
49 REAL, intent(inout):: ps(:, :) ! (iim + 1, jjm + 1) pression au sol, en Pa
50 REAL, intent(inout):: masse(:, :, :) ! (iim + 1, jjm + 1, llm) masse d'air
51 REAL, intent(in):: phis(:, :) ! (iim + 1, jjm + 1) surface geopotential
52
53 REAL, intent(inout):: q(:, :, :, :) ! (iim + 1, jjm + 1, llm, nqmx)
54 ! mass fractions of advected fields
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 INTEGER itau ! index of the time step of the dynamics, starts at 0
90 INTEGER itaufin
91 real finvmaold(iim + 1, jjm + 1, llm)
92 INTEGER l
93
94 ! Variables test conservation \'energie
95 REAL ecin(iim + 1, jjm + 1, llm), ecin0(iim + 1, jjm + 1, llm)
96
97 REAL vcont((iim + 1) * jjm, llm), ucont((iim + 1) * (jjm + 1), llm)
98 logical leapf
99 real dt ! time step, in s
100
101 !---------------------------------------------------
102
103 print *, "Call sequence information: leapfrog"
104 call assert(shape(ucov) == (/iim + 1, jjm + 1, llm/), "leapfrog")
105
106 itaufin = nday * day_step
107 ! "day_step" is a multiple of "iperiod", therefore so is "itaufin".
108
109 ! On initialise la pression et la fonction d'Exner :
110 forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps
111 CALL exner_hyb(ps, p3d, pks, pk, pkf)
112
113 time_integration: do itau = 0, itaufin - 1
114 leapf = mod(itau, iperiod) /= 0
115 if (leapf) then
116 dt = 2 * dtvr
117 else
118 ! Matsuno
119 dt = dtvr
120 if (ok_guide) call guide(itau, ucov, vcov, teta, q(:, :, :, 1), ps)
121 vcovm1 = vcov
122 ucovm1 = ucov
123 tetam1 = teta
124 massem1 = masse
125 psm1 = ps
126 finvmaold = masse
127 CALL filtreg(finvmaold, direct = .false., intensive = .false.)
128 end if
129
130 ! Calcul des tendances dynamiques:
131 CALL geopot(teta, pk, pks, phis, phi)
132 CALL caldyn(itau, ucov, vcov, teta, ps, masse, pk, pkf, phis, phi, &
133 dudyn, dv, dteta, dp, w, pbaru, pbarv, &
134 conser = MOD(itau, iconser) == 0)
135
136 CALL caladvtrac(q, pbaru, pbarv, p3d, masse, teta, pk)
137
138 ! Stokage du flux de masse pour traceurs offline:
139 IF (offline) CALL fluxstokenc(pbaru, pbarv, masse, teta, phi, phis, &
140 dtvr, itau)
141
142 ! Int\'egrations dynamique et traceurs:
143 CALL integrd(vcovm1, ucovm1, tetam1, psm1, massem1, dv, dudyn, dteta, &
144 dp, vcov, ucov, teta, q(:, :, :, :2), ps, masse, finvmaold, dt, &
145 leapf)
146
147 forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps
148 CALL exner_hyb(ps, p3d, pks, pk, pkf)
149
150 if (.not. leapf) then
151 ! Matsuno backward
152 ! Calcul des tendances dynamiques:
153 CALL geopot(teta, pk, pks, phis, phi)
154 CALL caldyn(itau + 1, ucov, vcov, teta, ps, masse, pk, pkf, phis, &
155 phi, dudyn, dv, dteta, dp, w, pbaru, pbarv, conser = .false.)
156
157 ! integrations dynamique et traceurs:
158 CALL integrd(vcovm1, ucovm1, tetam1, psm1, massem1, dv, dudyn, &
159 dteta, dp, vcov, ucov, teta, q(:, :, :, :2), ps, masse, &
160 finvmaold, dtvr, leapf=.false.)
161
162 forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps
163 CALL exner_hyb(ps, p3d, pks, pk, pkf)
164 end if
165
166 IF (MOD(itau + 1, iphysiq) == 0 .AND. iflag_phys /= 0) THEN
167 CALL calfis(itau / day_step + day_ini, &
168 REAL(mod(itau, day_step)) / day_step, ucov, vcov, teta, q, pk, &
169 phis, phi, w, dufi, dvfi, dtetafi, dqfi, &
170 lafin = itau + 1 == itaufin)
171
172 CALL addfi(ucov, vcov, teta, q, dufi, dvfi, dtetafi, dqfi)
173 ENDIF
174
175 IF (MOD(itau + 1, idissip) == 0) THEN
176 ! Dissipation horizontale et verticale des petites \'echelles
177
178 ! calcul de l'\'energie cin\'etique avant dissipation
179 call covcont(llm, ucov, vcov, ucont, vcont)
180 call enercin(vcov, ucov, vcont, ucont, ecin0)
181
182 ! dissipation
183 CALL dissip(vcov, ucov, teta, p3d, dvdis, dudis, dtetadis)
184 ucov = ucov + dudis
185 vcov = vcov + dvdis
186
187 ! On ajoute la tendance due \`a la transformation \'energie
188 ! cin\'etique en \'energie thermique par la dissipation
189 call covcont(llm, ucov, vcov, ucont, vcont)
190 call enercin(vcov, ucov, vcont, ucont, ecin)
191 dtetadis = dtetadis + (ecin0 - ecin) / pk
192 teta = teta + dtetadis
193
194 ! Calcul de la valeur moyenne aux p\^oles :
195 forall (l = 1: llm)
196 teta(:, 1, l) = SUM(aire_2d(:iim, 1) * teta(:iim, 1, l)) &
197 / apoln
198 teta(:, jjm + 1, l) = SUM(aire_2d(:iim, jjm+1) &
199 * teta(:iim, jjm + 1, l)) / apols
200 END forall
201 END IF
202
203 IF (MOD(itau + 1, iperiod) == 0) THEN
204 ! \'Ecriture du fichier histoire moyenne:
205 CALL writedynav(vcov, ucov, teta, pk, phi, q, masse, ps, phis, &
206 time = itau + 1)
207 call bilan_dyn(ps, masse, pk, pbaru, pbarv, teta, phi, ucov, vcov, &
208 q(:, :, :, 1))
209 ENDIF
210
211 IF (MOD(itau + 1, iecri * day_step) == 0) THEN
212 CALL geopot(teta, pk, pks, phis, phi)
213 CALL writehist(itau, vcov, ucov, teta, phi, q, masse, ps)
214 END IF
215 end do time_integration
216
217 CALL dynredem1("restart.nc", vcov, ucov, teta, q, masse, ps, &
218 itau = itau_dyn + itaufin)
219
220 ! Calcul des tendances dynamiques:
221 CALL geopot(teta, pk, pks, phis, phi)
222 CALL caldyn(itaufin, ucov, vcov, teta, ps, masse, pk, pkf, phis, phi, &
223 dudyn, dv, dteta, dp, w, pbaru, pbarv, &
224 conser = MOD(itaufin, iconser) == 0)
225
226 END SUBROUTINE leapfrog
227
228 end module leapfrog_m

  ViewVC Help
Powered by ViewVC 1.1.21