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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 20 - (hide annotations)
Wed Oct 15 16:19:57 2008 UTC (15 years, 7 months ago) by guez
Original Path: trunk/libf/phylmd/ini_hist.f90
File size: 19688 byte(s)
Deleted argument "presnivs" of "physiq", "ini_histhf", "ini_histhf3d",
"ini_histday", "ini_histins", "ini_histrac", "phytrac". Access it from
"comvert" instead.

Replaced calls to NetCDF Fortran 77 interface by calls to Fortran 90
interface or to NetCDF95.

Procedure "gr_phy_write_3d" now works with a variable of arbitrary
size in the second dimension.

Annotated use statements with "only" clause.

Replaced calls to NetCDF interface version 2 by calls to Fortran 90
interface in "guide.f90" and "read_reanalyse.f".

In "write_histrac", replaced calls to "gr_fi_ecrit" by calls to
"gr_phy_write_2d" and "gr_phy_write_3d".

1 guez 3 module ini_hist
2    
3     ! This module is clean: no C preprocessor directive, no include line.
4    
5     IMPLICIT none
6    
7     contains
8    
9 guez 20 subroutine ini_histhf(dtime, nid_hf, nid_hf3d)
10 guez 3
11     ! From phylmd/ini_histhf.h, version 1.3 2005/05/25 13:10:09
12    
13     use dimens_m, only: iim, jjm, llm
14     use temps, only: day_ref, annee_ref, itau_phy
15     use dimphy, only: klon
16     USE ioipsl, only: ymds2ju, histbeg_totreg, histvert, histend
17     use phyetat0_m, only: rlon, rlat
18 guez 20 use comvert, only: presnivs
19 guez 3
20     REAL, intent(in):: dtime ! pas temporel de la physique (s)
21     integer, intent(out):: nid_hf, nid_hf3d
22    
23     REAL zx_lon(iim, jjm + 1), zx_lat(iim, jjm + 1)
24     integer idayref
25     real zjulian
26     integer i, nhori, nvert
27    
28     !-----------------------------------------------
29    
30     idayref = day_ref
31     CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
32    
33     CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), rlon, zx_lon)
34     DO i = 1, iim
35     zx_lon(i, 1) = rlon(i+1)
36     zx_lon(i, (jjm + 1)) = rlon(i+1)
37     ENDDO
38    
39     CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), rlat, zx_lat)
40 guez 15 CALL histbeg_totreg("histhf", zx_lon(:, 1), zx_lat(1, :), 1, iim, 1, &
41     (jjm + 1), itau_phy, zjulian, dtime, nhori, nid_hf)
42 guez 3
43     CALL histvert(nid_hf, "presnivs", "Vertical levels", "mb", &
44     llm, presnivs/100., nvert)
45    
46 guez 20 call ini_histhf3d(dtime, nid_hf3d)
47 guez 3 CALL histend(nid_hf)
48    
49     end subroutine ini_histhf
50    
51     !******************************************************************
52    
53 guez 20 subroutine ini_histhf3d(dtime, nid_hf3d)
54 guez 3
55     ! From phylmd/ini_histhf3d.h, v 1.2 2005/05/25 13:10:09
56    
57     ! sorties hf 3d
58    
59     use dimens_m, only: iim, jjm, llm
60 guez 6 use dimphy, only: klon, nbtr
61 guez 3 use temps, only: itau_phy, day_ref, annee_ref
62     use clesphys, only: ecrit_hf
63     use phyetat0_m, only: rlon, rlat
64     USE ioipsl, only: ymds2ju, histbeg_totreg, histvert, histend, histdef
65 guez 20 use comvert, only: presnivs
66 guez 3
67     REAL, intent(in):: dtime ! pas temporel de la physique (s)
68     integer, intent(out):: nid_hf3d
69    
70     real zstohf, zout
71     REAL zx_lon(iim, jjm + 1), zx_lat(iim, jjm + 1)
72     real zjulian
73     integer i, nhori, nvert, idayref
74    
75     !------------------------------------------
76    
77     zstohf = dtime * REAL(ecrit_hf)
78     zout = dtime * REAL(ecrit_hf)
79    
80     idayref = day_ref
81     CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
82    
83     CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), rlon, zx_lon)
84     DO i = 1, iim
85     zx_lon(i, 1) = rlon(i+1)
86     zx_lon(i, (jjm + 1)) = rlon(i+1)
87     ENDDO
88    
89     CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), rlat, zx_lat)
90 guez 15 CALL histbeg_totreg("histhf3d", zx_lon(:, 1), zx_lat(1, :), 1, iim, 1, &
91     (jjm + 1), itau_phy, zjulian, dtime, nhori, nid_hf3d)
92 guez 3
93     CALL histvert(nid_hf3d, "presnivs", "Vertical levels", "mb", &
94     llm, presnivs/100., nvert)
95    
96     ! Champs 3D:
97    
98     CALL histdef(nid_hf3d, "temp", "Air temperature", "K", &
99 guez 15 iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
100 guez 3 "ave(X)", zstohf, zout)
101    
102     CALL histdef(nid_hf3d, "ovap", "Specific humidity", "kg/kg", &
103 guez 15 iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
104 guez 3 "ave(X)", zstohf, zout)
105    
106     CALL histdef(nid_hf3d, "vitu", "Zonal wind", "m/s", &
107 guez 15 iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
108 guez 3 "ave(X)", zstohf, zout)
109    
110     CALL histdef(nid_hf3d, "vitv", "Meridional wind", "m/s", &
111 guez 15 iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
112 guez 3 "ave(X)", zstohf, zout)
113    
114 guez 6 if (nbtr >= 3) then
115     CALL histdef(nid_hf3d, "O3", "Ozone mass fraction", "?", iim, &
116 guez 15 (jjm + 1), nhori, llm, 1, llm, nvert, "ave(X)", zstohf, &
117 guez 6 zout)
118     end if
119 guez 3
120     CALL histend(nid_hf3d)
121    
122     end subroutine ini_histhf3d
123    
124     !******************************************************************
125    
126 guez 20 subroutine ini_histday(dtime, ok_journe, nid_day, nq)
127 guez 3
128     ! From phylmd/ini_histday.h, v 1.3 2005/05/25 13:10:09
129    
130     use dimens_m, only: iim, jjm, llm
131     use temps, only: itau_phy, day_ref, annee_ref
132 guez 15 USE ioipsl, only: ymds2ju, histbeg_totreg, histvert, histend, histdef
133 guez 3 use phyetat0_m, only: rlon, rlat
134 guez 15 use clesphys, only: ecrit_day
135 guez 17 use grid_change, only: gr_phy_write_2d
136 guez 20 use comvert, only: presnivs
137 guez 3
138     REAL, intent(in):: dtime ! pas temporel de la physique (s)
139     logical, intent(in):: ok_journe
140     integer, intent(out):: nid_day
141 guez 17 INTEGER, intent(in):: nq ! nombre de traceurs (y compris vapeur d'eau)
142 guez 3
143 guez 17 ! Variables local to the procedure:
144     REAL zx_lat(iim, jjm + 1)
145     integer nhori, nvert
146 guez 3 real zjulian
147    
148     !--------------------------------
149    
150     IF (ok_journe) THEN
151 guez 17 CALL ymds2ju(annee_ref, 1, day_ref, 0., zjulian)
152     zx_lat = gr_phy_write_2d(rlat)
153     CALL histbeg_totreg("histday", rlon(2: iim+1), zx_lat(1, :), 1, iim, &
154     1, jjm + 1, itau_phy, zjulian, dtime, nhori, nid_day)
155 guez 3 CALL histvert(nid_day, "presnivs", "Vertical levels", "mb", &
156     llm, presnivs/100., nvert)
157 guez 17 if (nq <= 4) then
158     call histdef(nid_day, "Sigma_O3_Royer", &
159     "column-density of ozone, in a cell, from Royer", "DU", &
160     pxsize=iim, pysize=jjm+1, phoriid=nhori, pzsize=llm, &
161     par_oriz=1, par_szz=llm, pzid=nvert, popp="ave(X)", &
162     pfreq_opp=dtime, pfreq_wrt=real(ecrit_day))
163     end if
164 guez 3 CALL histend(nid_day)
165 guez 15 ENDIF
166 guez 3
167     end subroutine ini_histday
168    
169     !****************************************************
170    
171 guez 20 subroutine ini_histins(dtime, ok_instan, nid_ins)
172 guez 3
173     ! From phylmd/ini_histins.h, v 1.2 2005/05/25 13:10:09
174    
175     use dimens_m, only: iim, jjm, llm
176     use dimphy, only: klon
177     use temps, only: itau_phy, day_ref, annee_ref
178     use clesphys, only: ecrit_ins
179     use indicesol, only: nbsrf, clnsurf
180     USE ioipsl, only: ymds2ju, histbeg_totreg, histvert, histend, histdef
181     use phyetat0_m, only: rlon, rlat
182 guez 20 use comvert, only: presnivs
183 guez 3
184     REAL, intent(in):: dtime ! pas temporel de la physique (s)
185     logical, intent(in):: ok_instan
186     integer, intent(out):: nid_ins
187    
188     REAL zx_lon(iim, jjm + 1), zx_lat(iim, jjm + 1)
189     real zjulian, zsto, zout
190     integer i, nhori, nvert, idayref, nsrf
191    
192     !-------------------------------------------------------------------
193    
194     IF (ok_instan) THEN
195    
196     zsto = dtime * ecrit_ins
197     zout = dtime * ecrit_ins
198    
199     idayref = day_ref
200     CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
201    
202     CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), rlon, zx_lon)
203     DO i = 1, iim
204     zx_lon(i, 1) = rlon(i+1)
205     zx_lon(i, (jjm + 1)) = rlon(i+1)
206     ENDDO
207     CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), rlat, zx_lat)
208 guez 15 CALL histbeg_totreg("histins", zx_lon(:, 1), zx_lat(1, :), 1, iim, 1, &
209     jjm + 1, itau_phy, zjulian, dtime, nhori, nid_ins)
210 guez 3 write(*, *)'Inst ', itau_phy, zjulian
211     CALL histvert(nid_ins, "presnivs", "Vertical levels", "mb", &
212     llm, presnivs/100., nvert)
213    
214     CALL histdef(nid_ins, "phis", "Surface geop. height", "-", &
215 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
216 guez 3 "once", zsto, zout)
217    
218     CALL histdef(nid_ins, "aire", "Grid area", "-", &
219 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
220 guez 3 "once", zsto, zout)
221    
222     ! Champs 2D:
223    
224     CALL histdef(nid_ins, "tsol", "Surface Temperature", "K", &
225 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
226 guez 3 "inst(X)", zsto, zout)
227    
228     CALL histdef(nid_ins, "t2m", "Temperature 2m", "K", &
229 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
230 guez 3 "inst(X)", zsto, zout)
231    
232     CALL histdef(nid_ins, "q2m", "Specific humidity 2m", "Kg/Kg", &
233 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
234 guez 3 "inst(X)", zsto, zout)
235    
236     CALL histdef(nid_ins, "u10m", "Vent zonal 10m", "m/s", &
237 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
238 guez 3 "inst(X)", zsto, zout)
239    
240     CALL histdef(nid_ins, "v10m", "Vent meridien 10m", "m/s", &
241 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
242 guez 3 "inst(X)", zsto, zout)
243    
244     CALL histdef(nid_ins, "psol", "Surface Pressure", "Pa", &
245 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
246 guez 3 "inst(X)", zsto, zout)
247    
248     CALL histdef(nid_ins, "plul", "Large-scale Precip.", "mm/day", &
249 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
250 guez 3 "inst(X)", zsto, zout)
251    
252     CALL histdef(nid_ins, "pluc", "Convective Precip.", "mm/day", &
253 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
254 guez 3 "inst(X)", zsto, zout)
255    
256     CALL histdef(nid_ins, "cdrm", "Momentum drag coef.", "-", &
257 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
258 guez 3 "inst(X)", zsto, zout)
259    
260     CALL histdef(nid_ins, "cdrh", "Heat drag coef.", "-", &
261 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
262 guez 3 "inst(X)", zsto, zout)
263    
264     CALL histdef(nid_ins, "precip", "Precipitation Totale liq+sol", &
265     "kg/(s*m2)", &
266 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
267 guez 3 "inst(X)", zsto, zout)
268    
269     CALL histdef(nid_ins, "snow", "Snow fall", "kg/(s*m2)", &
270 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
271 guez 3 "inst(X)", zsto, zout)
272    
273     ! CALL histdef(nid_ins, "snow_mass", "Snow Mass", "kg/m2",
274 guez 15 ! . iim, (jjm + 1), nhori, 1, 1, 1, -99,
275 guez 3 ! . "inst(X)", zsto, zout)
276    
277     CALL histdef(nid_ins, "topl", "OLR", "W/m2", &
278 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
279 guez 3 "inst(X)", zsto, zout)
280    
281     CALL histdef(nid_ins, "evap", "Evaporation", "kg/(s*m2)", &
282 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
283 guez 3 "inst(X)", zsto, zout)
284    
285     CALL histdef(nid_ins, "sols", "Solar rad. at surf.", "W/m2", &
286 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
287 guez 3 "inst(X)", zsto, zout)
288    
289     CALL histdef(nid_ins, "soll", "IR rad. at surface", "W/m2", &
290 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
291 guez 3 "inst(X)", zsto, zout)
292    
293     CALL histdef(nid_ins, "solldown", "Down. IR rad. at surface", &
294 guez 15 "W/m2", iim, (jjm + 1), nhori, 1, 1, 1, -99, &
295 guez 3 "inst(X)", zsto, zout)
296    
297     CALL histdef(nid_ins, "bils", "Surf. total heat flux", "W/m2", &
298 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
299 guez 3 "inst(X)", zsto, zout)
300    
301     CALL histdef(nid_ins, "sens", "Sensible heat flux", "W/m2", &
302 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
303 guez 3 "inst(X)", zsto, zout)
304    
305     CALL histdef(nid_ins, "fder", "Heat flux derivation", "W/m2", &
306 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
307 guez 3 "inst(X)", zsto, zout)
308    
309     CALL histdef(nid_ins, "dtsvdfo", "Boundary-layer dTs(o)", "K/s", &
310 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
311 guez 3 "inst(X)", zsto, zout)
312    
313     CALL histdef(nid_ins, "dtsvdft", "Boundary-layer dTs(t)", "K/s", &
314 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
315 guez 3 "inst(X)", zsto, zout)
316    
317     CALL histdef(nid_ins, "dtsvdfg", "Boundary-layer dTs(g)", "K/s", &
318 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
319 guez 3 "inst(X)", zsto, zout)
320    
321     CALL histdef(nid_ins, "dtsvdfi", "Boundary-layer dTs(g)", "K/s", &
322 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
323 guez 3 "inst(X)", zsto, zout)
324    
325     DO nsrf = 1, nbsrf
326    
327     call histdef(nid_ins, "pourc_"//clnsurf(nsrf), &
328     "% "//clnsurf(nsrf), "%", &
329 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
330 guez 3 "inst(X)", zsto, zout)
331    
332     call histdef(nid_ins, "fract_"//clnsurf(nsrf), &
333     "Fraction "//clnsurf(nsrf), "1", &
334 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
335 guez 3 "inst(X)", zsto, zout)
336    
337     call histdef(nid_ins, "sens_"//clnsurf(nsrf), &
338     "Sensible heat flux "//clnsurf(nsrf), "W/m2", &
339 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
340 guez 3 "inst(X)", zsto, zout)
341    
342     call histdef(nid_ins, "tsol_"//clnsurf(nsrf), &
343     "Surface Temperature"//clnsurf(nsrf), "W/m2", &
344 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
345 guez 3 "inst(X)", zsto, zout)
346    
347     call histdef(nid_ins, "lat_"//clnsurf(nsrf), &
348     "Latent heat flux "//clnsurf(nsrf), "W/m2", &
349 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
350 guez 3 "inst(X)", zsto, zout)
351    
352     call histdef(nid_ins, "taux_"//clnsurf(nsrf), &
353     "Zonal wind stress"//clnsurf(nsrf), "Pa", &
354 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
355 guez 3 "inst(X)", zsto, zout)
356    
357     call histdef(nid_ins, "tauy_"//clnsurf(nsrf), &
358     "Meridional xind stress "//clnsurf(nsrf), "Pa", &
359 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
360 guez 3 "inst(X)", zsto, zout)
361    
362     call histdef(nid_ins, "albe_"//clnsurf(nsrf), &
363     "Albedo "//clnsurf(nsrf), "-", &
364 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
365 guez 3 "inst(X)", zsto, zout)
366    
367     call histdef(nid_ins, "rugs_"//clnsurf(nsrf), &
368     "rugosite "//clnsurf(nsrf), "-", &
369 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
370 guez 3 "inst(X)", zsto, zout)
371     !XXX
372     END DO
373     CALL histdef(nid_ins, "rugs", "rugosity", "-", &
374 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
375 guez 3 "inst(X)", zsto, zout)
376    
377     CALL histdef(nid_ins, "albs", "Surface albedo", "-", &
378 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
379 guez 3 "inst(X)", zsto, zout)
380     CALL histdef(nid_ins, "albslw", "Surface albedo LW", "-", &
381 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
382 guez 3 "inst(X)", zsto, zout)
383    
384     !IM cf. AM 081204 BEG
385     ! HBTM2
386     CALL histdef(nid_ins, "s_pblh", "Boundary Layer Height", "m", &
387 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
388 guez 3 "inst(X)", zsto, zout)
389    
390     CALL histdef(nid_ins, "s_pblt", "T at Boundary Layer Height", &
391     "K", &
392 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
393 guez 3 "inst(X)", zsto, zout)
394    
395     CALL histdef(nid_ins, "s_lcl", "Condensation level", "m", &
396 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
397 guez 3 "inst(X)", zsto, zout)
398    
399     CALL histdef(nid_ins, "s_capCL", "Conv avlbl pot ener for ABL", "J/m2", &
400 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
401 guez 3 "inst(X)", zsto, zout)
402    
403     CALL histdef(nid_ins, "s_oliqCL", "Liq Water in BL", "kg/m2", &
404 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
405 guez 3 "inst(X)", zsto, zout)
406    
407     CALL histdef(nid_ins, "s_cteiCL", "Instability criteria (ABL)", "K", &
408 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
409 guez 3 "inst(X)", zsto, zout)
410    
411     CALL histdef(nid_ins, "s_therm", "Exces du thermique", "K", &
412 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
413 guez 3 "inst(X)", zsto, zout)
414    
415     CALL histdef(nid_ins, "s_trmb1", "deep_cape(HBTM2)", "J/m2", &
416 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
417 guez 3 "inst(X)", zsto, zout)
418    
419     CALL histdef(nid_ins, "s_trmb2", "inhibition (HBTM2)", "J/m2", &
420 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
421 guez 3 "inst(X)", zsto, zout)
422    
423     CALL histdef(nid_ins, "s_trmb3", "Point Omega (HBTM2)", "m", &
424 guez 15 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
425 guez 3 "inst(X)", zsto, zout)
426    
427     !IM cf. AM 081204 END
428    
429     ! Champs 3D:
430    
431     CALL histdef(nid_ins, "temp", "Temperature", "K", &
432 guez 15 iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
433 guez 3 "inst(X)", zsto, zout)
434    
435     CALL histdef(nid_ins, "vitu", "Zonal wind", "m/s", &
436 guez 15 iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
437 guez 3 "inst(X)", zsto, zout)
438    
439     CALL histdef(nid_ins, "vitv", "Merid wind", "m/s", &
440 guez 15 iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
441 guez 3 "inst(X)", zsto, zout)
442    
443     CALL histdef(nid_ins, "geop", "Geopotential height", "m", &
444 guez 15 iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
445 guez 3 "inst(X)", zsto, zout)
446    
447     CALL histdef(nid_ins, "pres", "Air pressure", "Pa", &
448 guez 15 iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
449 guez 3 "inst(X)", zsto, zout)
450    
451     CALL histdef(nid_ins, "dtvdf", "Boundary-layer dT", "K/s", &
452 guez 15 iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
453 guez 3 "inst(X)", zsto, zout)
454    
455     CALL histdef(nid_ins, "dqvdf", "Boundary-layer dQ", "Kg/Kg/s", &
456 guez 15 iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
457 guez 3 "inst(X)", zsto, zout)
458    
459     CALL histend(nid_ins)
460     ENDIF
461    
462     end subroutine ini_histins
463    
464 guez 17 !*************************************************
465    
466 guez 20 subroutine ini_histrac(nid_tra, pdtphys, nq_phys, lessivage)
467 guez 17
468     ! From phylmd/ini_histrac.h, version 1.10 2006/02/21 08:08:30
469    
470     use dimens_m, only: iim, jjm, llm
471     use ioipsl, only: ymds2ju, histbeg_totreg, histvert, histdef, histend
472     use temps, only: annee_ref, day_ref, itau_phy
473 guez 18 use iniadvtrac_m, only: niadv, tnom, ttext
474 guez 17 use dimphy, only: klon
475     use clesphys, only: ecrit_tra
476     use grid_change, only: gr_phy_write_2d
477     use phyetat0_m, only: rlon, rlat
478 guez 20 use comvert, only: presnivs
479 guez 17
480     INTEGER, intent(out):: nid_tra
481     real, intent(in):: pdtphys ! pas d'integration pour la physique (s)
482    
483 guez 18 integer, intent(in):: nq_phys
484 guez 17 ! (nombre de traceurs auxquels on applique la physique)
485    
486     logical, intent(in):: lessivage
487    
488     ! Variables local to the procedure:
489    
490     REAL zjulian
491     REAL zx_lat(iim, jjm+1)
492     INTEGER nhori, nvert
493     REAL zsto, zout
494     integer it, iq, iiq
495    
496     !---------------------------------------------------------
497    
498     CALL ymds2ju(annee_ref, month=1, day=day_ref, sec=0.0, julian=zjulian)
499     zx_lat(:, :) = gr_phy_write_2d(rlat)
500     CALL histbeg_totreg("histrac", rlon(2:iim+1), zx_lat(1, :), &
501     1, iim, 1, jjm+1, itau_phy, zjulian, pdtphys, nhori, nid_tra)
502     CALL histvert(nid_tra, "presnivs", "Vertical levels", "mb", llm, &
503     presnivs, nvert)
504    
505     zsto = pdtphys
506     zout = pdtphys * REAL(ecrit_tra)
507    
508     CALL histdef(nid_tra, "phis", "Surface geop. height", "-", &
509     iim, jjm+1, nhori, 1, 1, 1, -99, &
510     "once", zsto, zout)
511     CALL histdef(nid_tra, "aire", "Grid area", "-", &
512     iim, jjm+1, nhori, 1, 1, 1, -99, &
513     "once", zsto, zout)
514     CALL histdef(nid_tra, "zmasse", "column density of air in cell", &
515     "kg m-2", iim, jjm + 1, nhori, llm, 1, llm, nvert, "ave(X)", &
516     zsto, zout)
517    
518 guez 18 DO it = 1, nq_phys
519 guez 17 ! champ 2D
520     iq=it+2
521     iiq=niadv(iq)
522     CALL histdef(nid_tra, tnom(iq), ttext(iiq), "U/kga", iim, jjm+1, &
523     nhori, llm, 1, llm, nvert, "ave(X)", zsto, zout)
524     if (lessivage) THEN
525     CALL histdef(nid_tra, "fl"//tnom(iq), "Flux "//ttext(iiq), &
526     "U/m2/s", iim, jjm+1, nhori, llm, 1, llm, nvert, &
527     "ave(X)", zsto, zout)
528     endif
529    
530     !---Ajout Olivia
531     CALL histdef(nid_tra, "d_tr_th_"//tnom(iq), &
532     "tendance thermique"// ttext(iiq), "?", &
533     iim, jjm+1, nhori, llm, 1, llm, nvert, &
534     "ave(X)", zsto, zout)
535     CALL histdef(nid_tra, "d_tr_cv_"//tnom(iq), &
536     "tendance convection"// ttext(iiq), "?", &
537     iim, jjm+1, nhori, llm, 1, llm, nvert, &
538     "ave(X)", zsto, zout)
539     CALL histdef(nid_tra, "d_tr_cl_"//tnom(iq), &
540     "tendance couche limite"// ttext(iiq), "?", &
541     iim, jjm+1, nhori, llm, 1, llm, nvert, &
542     "ave(X)", zsto, zout)
543     !---fin Olivia
544    
545     ENDDO
546    
547     CALL histdef(nid_tra, "pplay", "", "-", &
548     iim, jjm+1, nhori, llm, 1, llm, nvert, &
549     "inst(X)", zout, zout)
550     CALL histdef(nid_tra, "t", "", "-", &
551     iim, jjm+1, nhori, llm, 1, llm, nvert, &
552     "inst(X)", zout, zout)
553    
554     CALL histend(nid_tra)
555    
556     end subroutine ini_histrac
557    
558 guez 3 end module ini_hist

  ViewVC Help
Powered by ViewVC 1.1.21