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

Contents of /trunk/dyn3d/leapfrog.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 129 - (show annotations)
Fri Feb 13 18:22:38 2015 UTC (9 years, 3 months ago) by guez
File size: 8534 byte(s)
Removed arguments day0, anne0 of procedures initdynav and
inithist. Use directly day_ref, annee_ref instead.

Moved variables annee_ref, day_ref of module temps to module
dynetat0_m. Deleted variables dayref and anneeref of module conf_gcm_m
and removed them from namelist conf_gcm_nml. These variables were
troubling intermediary on the way to annee_ref and day_ref. Gave as
default values to annee_ref and day_ref the default values of dayref
and anneeref. Moved the test on raz_date from main unit gcm to
procedure dynetat0. Created namelist dynetat0_nml. Read annee_ref and
day_ref from standard input in dynetat0 and redefine them from
"start.nc" if not raz_date. Rationale: 1 - Choose the best programming
from the point of view of program gcm only, forgetting program ce0l. 2
- The normal case is to define annee_ref and day_ref from "start.nc"
so put them in module dynetat0_m rather than in conf_gcm_m. 3 - Try to
always read the same namelists in the same order regardless of choices
in previous namelists. Downsides: 1 -We now need the file "dynetat0.f"
for the program ce0l, because dynetat0_m is used by dynredem0. 2 - We
need to define annee_ref and day_ref from procedure etat0.

Removed useless variable day_end of module temps.

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 time ! time of day, as a fraction of day length
92 real finvmaold(iim + 1, jjm + 1, llm)
93 INTEGER l
94
95 ! Variables test conservation \'energie
96 REAL ecin(iim + 1, jjm + 1, llm), ecin0(iim + 1, jjm + 1, llm)
97
98 REAL vcont((iim + 1) * jjm, llm), ucont((iim + 1) * (jjm + 1), llm)
99 logical leapf
100 real dt ! time step, in s
101
102 !---------------------------------------------------
103
104 print *, "Call sequence information: leapfrog"
105 call assert(shape(ucov) == (/iim + 1, jjm + 1, llm/), "leapfrog")
106
107 itaufin = nday * day_step
108 ! "day_step" is a multiple of "iperiod", therefore so is "itaufin".
109
110 ! On initialise la pression et la fonction d'Exner :
111 forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps
112 CALL exner_hyb(ps, p3d, pks, pk, pkf)
113
114 time_integration: do itau = 0, itaufin - 1
115 leapf = mod(itau, iperiod) /= 0
116 if (leapf) then
117 dt = 2 * dtvr
118 else
119 ! Matsuno
120 dt = dtvr
121 if (ok_guide) call guide(itau, ucov, vcov, teta, q(:, :, :, 1), ps)
122 vcovm1 = vcov
123 ucovm1 = ucov
124 tetam1 = teta
125 massem1 = masse
126 psm1 = ps
127 finvmaold = masse
128 CALL filtreg(finvmaold, direct = .false., intensive = .false.)
129 end if
130
131 ! Calcul des tendances dynamiques:
132 CALL geopot(teta, pk, pks, phis, phi)
133 CALL caldyn(itau, ucov, vcov, teta, ps, masse, pk, pkf, phis, phi, &
134 dudyn, dv, dteta, dp, w, pbaru, pbarv, &
135 conser = MOD(itau, iconser) == 0)
136
137 CALL caladvtrac(q, pbaru, pbarv, p3d, masse, teta, pk)
138
139 ! Stokage du flux de masse pour traceurs offline:
140 IF (offline) CALL fluxstokenc(pbaru, pbarv, masse, teta, phi, phis, &
141 dtvr, itau)
142
143 ! Int\'egrations dynamique et traceurs:
144 CALL integrd(vcovm1, ucovm1, tetam1, psm1, massem1, dv, dudyn, dteta, &
145 dp, vcov, ucov, teta, q(:, :, :, :2), ps, masse, finvmaold, dt, &
146 leapf)
147
148 forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps
149 CALL exner_hyb(ps, p3d, pks, pk, pkf)
150
151 if (.not. leapf) then
152 ! Matsuno backward
153 ! Calcul des tendances dynamiques:
154 CALL geopot(teta, pk, pks, phis, phi)
155 CALL caldyn(itau + 1, ucov, vcov, teta, ps, masse, pk, pkf, phis, &
156 phi, dudyn, dv, dteta, dp, w, pbaru, pbarv, conser = .false.)
157
158 ! integrations dynamique et traceurs:
159 CALL integrd(vcovm1, ucovm1, tetam1, psm1, massem1, dv, dudyn, &
160 dteta, dp, vcov, ucov, teta, q(:, :, :, :2), ps, masse, &
161 finvmaold, dtvr, leapf=.false.)
162
163 forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps
164 CALL exner_hyb(ps, p3d, pks, pk, pkf)
165 end if
166
167 IF (MOD(itau + 1, iphysiq) == 0 .AND. iflag_phys /= 0) THEN
168 ! Calcul des tendances physiques :
169 time = REAL(mod(itau, day_step)) / day_step
170 IF (time > 1.) time = time - 1.
171 CALL calfis(itau * dtvr / daysec + day_ini, time, ucov, vcov, teta, &
172 q, pk, phis, phi, w, dufi, dvfi, dtetafi, dqfi, &
173 lafin = itau + 1 == itaufin)
174
175 CALL addfi(ucov, vcov, teta, q, dufi, dvfi, dtetafi, dqfi)
176 ENDIF
177
178 IF (MOD(itau + 1, idissip) == 0) THEN
179 ! Dissipation horizontale et verticale des petites \'echelles
180
181 ! calcul de l'\'energie cin\'etique avant dissipation
182 call covcont(llm, ucov, vcov, ucont, vcont)
183 call enercin(vcov, ucov, vcont, ucont, ecin0)
184
185 ! dissipation
186 CALL dissip(vcov, ucov, teta, p3d, dvdis, dudis, dtetadis)
187 ucov = ucov + dudis
188 vcov = vcov + dvdis
189
190 ! On ajoute la tendance due \`a la transformation \'energie
191 ! cin\'etique en \'energie thermique par la dissipation
192 call covcont(llm, ucov, vcov, ucont, vcont)
193 call enercin(vcov, ucov, vcont, ucont, ecin)
194 dtetadis = dtetadis + (ecin0 - ecin) / pk
195 teta = teta + dtetadis
196
197 ! Calcul de la valeur moyenne aux p\^oles :
198 forall (l = 1: llm)
199 teta(:, 1, l) = SUM(aire_2d(:iim, 1) * teta(:iim, 1, l)) &
200 / apoln
201 teta(:, jjm + 1, l) = SUM(aire_2d(:iim, jjm+1) &
202 * teta(:iim, jjm + 1, l)) / apols
203 END forall
204 END IF
205
206 IF (MOD(itau + 1, iperiod) == 0) THEN
207 ! \'Ecriture du fichier histoire moyenne:
208 CALL writedynav(vcov, ucov, teta, pk, phi, q, masse, ps, phis, &
209 time = itau + 1)
210 call bilan_dyn(ps, masse, pk, pbaru, pbarv, teta, phi, ucov, vcov, &
211 q(:, :, :, 1))
212 ENDIF
213
214 IF (MOD(itau + 1, iecri * day_step) == 0) THEN
215 CALL geopot(teta, pk, pks, phis, phi)
216 CALL writehist(itau, vcov, ucov, teta, phi, q, masse, ps)
217 END IF
218 end do time_integration
219
220 CALL dynredem1("restart.nc", vcov, ucov, teta, q, masse, ps, &
221 itau = itau_dyn + itaufin)
222
223 ! Calcul des tendances dynamiques:
224 CALL geopot(teta, pk, pks, phis, phi)
225 CALL caldyn(itaufin, ucov, vcov, teta, ps, masse, pk, pkf, phis, phi, &
226 dudyn, dv, dteta, dp, w, pbaru, pbarv, &
227 conser = MOD(itaufin, iconser) == 0)
228
229 END SUBROUTINE leapfrog
230
231 end module leapfrog_m

  ViewVC Help
Powered by ViewVC 1.1.21