/[lmdze]/trunk/libf/phylmd/phystokenc.f90
ViewVC logotype

Annotation of /trunk/libf/phylmd/phystokenc.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 32 - (hide annotations)
Tue Apr 6 17:52:58 2010 UTC (14 years, 1 month ago) by guez
File size: 11025 byte(s)
Split "stringop.f90" into single-procedure files. Gathered files in directory
"IOIPSL/Stringop".

Split "flincom.f90" into "flincom.f90" and "flinget.f90". Removed
unused procedures from module "flincom". Removed unused argument
"filename" of procedure "flinopen_nozoom".

Removed unused files.

Split "grid_change.f90" into "grid_change.f90" and
"gr_phy_write_3d.f90".

Removed unused procedures from modules "calendar", "ioipslmpp",
"grid_atob", "gath_cpl" and "getincom". Removed unused procedures in
files "ppm3d.f" and "thermcell.f".

Split "mathelp.f90" into "mathelp.f90" and "mathop.f90".

Removed unused variable "dpres" of module "comvert".

Use argument "itau" instead of local variables "iadvtr" and "first" to
control algorithm in procedure "fluxstokenc".

Removed unused arguments of procedure "integrd".

Removed useless computations at the end of procedure "leapfrog".

Merged common block "matrfil" into module "parafilt".

1 guez 32 module phystokenc_m
2 guez 3
3 guez 32 IMPLICIT NONE
4 guez 3
5 guez 32 contains
6 guez 3
7 guez 32 SUBROUTINE phystokenc(pdtphys, rlon, rlat, pt, pmfu, pmfd, pen_u, pde_u, &
8     pen_d, pde_d, pfm_therm, pentr_therm, pcoefh, yu1, yv1, ftsol, pctsrf, &
9     frac_impa, frac_nucl, pphis, paire, dtime, itap)
10 guez 3
11 guez 32 ! From phylmd/phystokenc.F, version 1.2 2004/06/22 11:45:35
12     ! Author: Frédéric Hourdin
13     ! Objet: moniteur général des tendances traceurs
14 guez 3
15 guez 32 USE histwrite_m, ONLY : histwrite
16     USE histcom, ONLY : histsync
17     USE dimens_m, ONLY : iim, jjm, nqmx
18     USE indicesol, ONLY : nbsrf
19     USE dimphy, ONLY : klev, klon
20     USE tracstoke, ONLY : istphy
21 guez 3
22 guez 32 ! Arguments:
23 guez 3
24 guez 32 ! EN ENTREE:
25 guez 3
26 guez 32 ! divers:
27 guez 3
28 guez 32 REAL, INTENT (IN) :: pdtphys ! pas d'integration pour la physique (seconde)
29     INTEGER, INTENT (IN) :: itap
30 guez 3
31 guez 32 ! convection:
32 guez 3
33 guez 32 REAL pmfu(klon, klev) ! flux de masse dans le panache montant
34     REAL pmfd(klon, klev) ! flux de masse dans le panache descendant
35     REAL pen_u(klon, klev) ! flux entraine dans le panache montant
36     REAL pde_u(klon, klev) ! flux detraine dans le panache montant
37     REAL pen_d(klon, klev) ! flux entraine dans le panache descendant
38     REAL pde_d(klon, klev) ! flux detraine dans le panache descendant
39     REAL pt(klon, klev)
40 guez 3
41 guez 32 REAL, INTENT (IN) :: rlon(klon), rlat(klon)
42     REAL, INTENT (IN) :: dtime
43 guez 3
44 guez 32 ! Les Thermiques
45     REAL pfm_therm(klon, klev+1)
46     REAL pentr_therm(klon, klev)
47 guez 3
48 guez 32 ! Couche limite:
49 guez 3
50 guez 32 REAL yv1(klon)
51     REAL yu1(klon), pphis(klon), paire(klon)
52     REAL pcoefh(klon, klev) ! coeff melange Couche limite
53 guez 3
54 guez 32 ! Arguments necessaires pour les sources et puits de traceur
55 guez 3
56 guez 32 REAL ftsol(klon, nbsrf) ! Temperature du sol (surf)(Kelvin)
57     REAL pctsrf(klon, nbsrf) ! Pourcentage de sol f(nature du sol)
58 guez 3
59 guez 32 ! Lessivage:
60 guez 3
61 guez 32 REAL frac_impa(klon, klev)
62     REAL frac_nucl(klon, klev)
63 guez 3
64 guez 32 ! Variables local to the procedure:
65 guez 3
66 guez 32 real t(klon, klev)
67     INTEGER, SAVE:: physid
68     REAL zx_tmp_3d(iim, jjm+1, klev), zx_tmp_2d(iim, jjm+1)
69 guez 3
70 guez 32 ! Les Thermiques
71 guez 3
72 guez 32 REAL fm_therm1(klon, klev)
73     REAL entr_therm(klon, klev)
74     REAL fm_therm(klon, klev)
75 guez 3
76 guez 32 INTEGER i, k
77 guez 3
78 guez 32 REAL mfu(klon, klev) ! flux de masse dans le panache montant
79     REAL mfd(klon, klev) ! flux de masse dans le panache descendant
80     REAL en_u(klon, klev) ! flux entraine dans le panache montant
81     REAL de_u(klon, klev) ! flux detraine dans le panache montant
82     REAL en_d(klon, klev) ! flux entraine dans le panache descendant
83     REAL de_d(klon, klev) ! flux detraine dans le panache descendant
84     REAL coefh(klon, klev) ! flux detraine dans le panache descendant
85 guez 3
86 guez 32 REAL pyu1(klon), pyv1(klon)
87     REAL pftsol(klon, nbsrf), ppsrf(klon, nbsrf)
88     REAL pftsol1(klon), pftsol2(klon), pftsol3(klon), pftsol4(klon)
89     REAL ppsrf1(klon), ppsrf2(klon), ppsrf3(klon), ppsrf4(klon)
90 guez 3
91 guez 32 REAL dtcum
92 guez 3
93 guez 32 INTEGER iadvtr, irec
94     REAL zmin, zmax
95     LOGICAL ok_sync
96 guez 3
97 guez 32 SAVE t, mfu, mfd, en_u, de_u, en_d, de_d, coefh, dtcum
98     SAVE fm_therm, entr_therm
99     SAVE iadvtr, irec
100     SAVE pyu1, pyv1, pftsol, ppsrf
101 guez 3
102 guez 32 DATA iadvtr, irec/0, 1/
103 guez 3
104 guez 32 !------------------------------------------------------
105 guez 3
106 guez 32 ! Couche limite:
107    
108     ok_sync = .TRUE.
109    
110     IF (iadvtr==0) THEN
111     CALL initphysto('phystoke', rlon, rlat, dtime, dtime*istphy, &
112     dtime*istphy, nqmx, physid)
113     END IF
114    
115     i = itap
116     CALL gr_fi_ecrit(1, klon, iim, jjm+1, pphis, zx_tmp_2d)
117     CALL histwrite(physid, 'phis', i, zx_tmp_2d)
118    
119     i = itap
120     CALL gr_fi_ecrit(1, klon, iim, jjm+1, paire, zx_tmp_2d)
121     CALL histwrite(physid, 'aire', i, zx_tmp_2d)
122    
123     iadvtr = iadvtr + 1
124    
125     IF (mod(iadvtr, istphy)==1 .OR. istphy==1) THEN
126     PRINT *, 'reinitialisation des champs cumules a iadvtr=', iadvtr
127     DO k = 1, klev
128     DO i = 1, klon
129     mfu(i, k) = 0.
130     mfd(i, k) = 0.
131     en_u(i, k) = 0.
132     de_u(i, k) = 0.
133     en_d(i, k) = 0.
134     de_d(i, k) = 0.
135     coefh(i, k) = 0.
136     t(i, k) = 0.
137     fm_therm(i, k) = 0.
138     entr_therm(i, k) = 0.
139     END DO
140     END DO
141     DO i = 1, klon
142     pyv1(i) = 0.
143     pyu1(i) = 0.
144     END DO
145     DO k = 1, nbsrf
146     DO i = 1, klon
147     pftsol(i, k) = 0.
148     ppsrf(i, k) = 0.
149     END DO
150     END DO
151    
152     dtcum = 0.
153     END IF
154    
155     DO k = 1, klev
156     DO i = 1, klon
157     mfu(i, k) = mfu(i, k) + pmfu(i, k)*pdtphys
158     mfd(i, k) = mfd(i, k) + pmfd(i, k)*pdtphys
159     en_u(i, k) = en_u(i, k) + pen_u(i, k)*pdtphys
160     de_u(i, k) = de_u(i, k) + pde_u(i, k)*pdtphys
161     en_d(i, k) = en_d(i, k) + pen_d(i, k)*pdtphys
162     de_d(i, k) = de_d(i, k) + pde_d(i, k)*pdtphys
163     coefh(i, k) = coefh(i, k) + pcoefh(i, k)*pdtphys
164     t(i, k) = t(i, k) + pt(i, k)*pdtphys
165     fm_therm(i, k) = fm_therm(i, k) + pfm_therm(i, k)*pdtphys
166     entr_therm(i, k) = entr_therm(i, k) + pentr_therm(i, k)*pdtphys
167     END DO
168     END DO
169     DO i = 1, klon
170     pyv1(i) = pyv1(i) + yv1(i)*pdtphys
171     pyu1(i) = pyu1(i) + yu1(i)*pdtphys
172     END DO
173     DO k = 1, nbsrf
174     DO i = 1, klon
175     pftsol(i, k) = pftsol(i, k) + ftsol(i, k)*pdtphys
176     ppsrf(i, k) = ppsrf(i, k) + pctsrf(i, k)*pdtphys
177     END DO
178     END DO
179    
180     dtcum = dtcum + pdtphys
181    
182     IF (mod(iadvtr, istphy)==0) THEN
183     ! normalisation par le temps cumule
184     DO k = 1, klev
185     DO i = 1, klon
186     mfu(i, k) = mfu(i, k)/dtcum
187     mfd(i, k) = mfd(i, k)/dtcum
188     en_u(i, k) = en_u(i, k)/dtcum
189     de_u(i, k) = de_u(i, k)/dtcum
190     en_d(i, k) = en_d(i, k)/dtcum
191     de_d(i, k) = de_d(i, k)/dtcum
192     coefh(i, k) = coefh(i, k)/dtcum
193     ! Unitel a enlever
194     t(i, k) = t(i, k)/dtcum
195     fm_therm(i, k) = fm_therm(i, k)/dtcum
196     entr_therm(i, k) = entr_therm(i, k)/dtcum
197     END DO
198     END DO
199     DO i = 1, klon
200     pyv1(i) = pyv1(i)/dtcum
201     pyu1(i) = pyu1(i)/dtcum
202     END DO
203     DO k = 1, nbsrf
204     DO i = 1, klon
205     pftsol(i, k) = pftsol(i, k)/dtcum
206     pftsol1(i) = pftsol(i, 1)
207     pftsol2(i) = pftsol(i, 2)
208     pftsol3(i) = pftsol(i, 3)
209     pftsol4(i) = pftsol(i, 4)
210    
211     ppsrf(i, k) = ppsrf(i, k)/dtcum
212     ppsrf1(i) = ppsrf(i, 1)
213     ppsrf2(i) = ppsrf(i, 2)
214     ppsrf3(i) = ppsrf(i, 3)
215     ppsrf4(i) = ppsrf(i, 4)
216    
217     END DO
218     END DO
219    
220     ! ecriture des champs
221    
222     irec = irec + 1
223    
224     !cccc
225     CALL gr_fi_ecrit(klev, klon, iim, jjm+1, t, zx_tmp_3d)
226     CALL histwrite(physid, 't', itap, zx_tmp_3d)
227    
228     CALL gr_fi_ecrit(klev, klon, iim, jjm+1, mfu, zx_tmp_3d)
229     CALL histwrite(physid, 'mfu', itap, zx_tmp_3d)
230     CALL gr_fi_ecrit(klev, klon, iim, jjm+1, mfd, zx_tmp_3d)
231     CALL histwrite(physid, 'mfd', itap, zx_tmp_3d)
232     CALL gr_fi_ecrit(klev, klon, iim, jjm+1, en_u, zx_tmp_3d)
233     CALL histwrite(physid, 'en_u', itap, zx_tmp_3d)
234     CALL gr_fi_ecrit(klev, klon, iim, jjm+1, de_u, zx_tmp_3d)
235     CALL histwrite(physid, 'de_u', itap, zx_tmp_3d)
236     CALL gr_fi_ecrit(klev, klon, iim, jjm+1, en_d, zx_tmp_3d)
237     CALL histwrite(physid, 'en_d', itap, zx_tmp_3d)
238     CALL gr_fi_ecrit(klev, klon, iim, jjm+1, de_d, zx_tmp_3d)
239     CALL histwrite(physid, 'de_d', itap, zx_tmp_3d)
240     CALL gr_fi_ecrit(klev, klon, iim, jjm+1, coefh, zx_tmp_3d)
241     CALL histwrite(physid, 'coefh', itap, zx_tmp_3d)
242    
243     ! ajou...
244     DO k = 1, klev
245     DO i = 1, klon
246     fm_therm1(i, k) = fm_therm(i, k)
247     END DO
248     END DO
249    
250     CALL gr_fi_ecrit(klev, klon, iim, jjm+1, fm_therm1, zx_tmp_3d)
251     CALL histwrite(physid, 'fm_th', itap, zx_tmp_3d)
252    
253     CALL gr_fi_ecrit(klev, klon, iim, jjm+1, entr_therm, zx_tmp_3d)
254     CALL histwrite(physid, 'en_th', itap, zx_tmp_3d)
255     !ccc
256     CALL gr_fi_ecrit(klev, klon, iim, jjm+1, frac_impa, zx_tmp_3d)
257     CALL histwrite(physid, 'frac_impa', itap, zx_tmp_3d)
258    
259     CALL gr_fi_ecrit(klev, klon, iim, jjm+1, frac_nucl, zx_tmp_3d)
260     CALL histwrite(physid, 'frac_nucl', itap, zx_tmp_3d)
261    
262     CALL gr_fi_ecrit(1, klon, iim, jjm+1, pyu1, zx_tmp_2d)
263     CALL histwrite(physid, 'pyu1', itap, zx_tmp_2d)
264    
265     CALL gr_fi_ecrit(1, klon, iim, jjm+1, pyv1, zx_tmp_2d)
266     CALL histwrite(physid, 'pyv1', itap, zx_tmp_2d)
267    
268     CALL gr_fi_ecrit(1, klon, iim, jjm+1, pftsol1, zx_tmp_2d)
269     CALL histwrite(physid, 'ftsol1', itap, zx_tmp_2d)
270     CALL gr_fi_ecrit(1, klon, iim, jjm+1, pftsol2, zx_tmp_2d)
271     CALL histwrite(physid, 'ftsol2', itap, zx_tmp_2d)
272     CALL gr_fi_ecrit(1, klon, iim, jjm+1, pftsol3, zx_tmp_2d)
273     CALL histwrite(physid, 'ftsol3', itap, zx_tmp_2d)
274     CALL gr_fi_ecrit(1, klon, iim, jjm+1, pftsol4, zx_tmp_2d)
275     CALL histwrite(physid, 'ftsol4', itap, zx_tmp_2d)
276    
277     CALL gr_fi_ecrit(1, klon, iim, jjm+1, ppsrf1, zx_tmp_2d)
278     CALL histwrite(physid, 'psrf1', itap, zx_tmp_2d)
279     CALL gr_fi_ecrit(1, klon, iim, jjm+1, ppsrf2, zx_tmp_2d)
280     CALL histwrite(physid, 'psrf2', itap, zx_tmp_2d)
281     CALL gr_fi_ecrit(1, klon, iim, jjm+1, ppsrf3, zx_tmp_2d)
282     CALL histwrite(physid, 'psrf3', itap, zx_tmp_2d)
283     CALL gr_fi_ecrit(1, klon, iim, jjm+1, ppsrf4, zx_tmp_2d)
284     CALL histwrite(physid, 'psrf4', itap, zx_tmp_2d)
285    
286     IF (ok_sync) CALL histsync(physid)
287     ! if (ok_sync) call histsync
288    
289    
290     !AA Test sur la valeur des coefficients de lessivage
291    
292     zmin = 1E33
293     zmax = -1E33
294     DO k = 1, klev
295     DO i = 1, klon
296     zmax = max(zmax, frac_nucl(i, k))
297     zmin = min(zmin, frac_nucl(i, k))
298     END DO
299     END DO
300     PRINT *, '------ coefs de lessivage (min et max) --------'
301     PRINT *, 'facteur de nucleation ', zmin, zmax
302     zmin = 1E33
303     zmax = -1E33
304     DO k = 1, klev
305     DO i = 1, klon
306     zmax = max(zmax, frac_impa(i, k))
307     zmin = min(zmin, frac_impa(i, k))
308     END DO
309     END DO
310     PRINT *, 'facteur d impaction ', zmin, zmax
311    
312     END IF
313    
314     END SUBROUTINE phystokenc
315    
316     end module phystokenc_m

  ViewVC Help
Powered by ViewVC 1.1.21