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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 6 - (hide annotations)
Tue Mar 4 14:00:42 2008 UTC (16 years, 2 months ago) by guez
File size: 16620 byte(s)
Removed test on coefoz_LMDZ in gcm.sh.
Added test on nbtr in ini_histhf3d and write_histhf3d.
Added test on nqmax in phytrac.
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     subroutine ini_histhf(dtime, presnivs, nid_hf, nid_hf3d)
10    
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    
19     REAL, intent(in):: dtime ! pas temporel de la physique (s)
20     real, intent(in):: presnivs(:)
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     CALL histbeg_totreg("histhf", iim, zx_lon(:, 1), (jjm + 1), &
41     zx_lat(1, :), 1, iim, 1, (jjm + 1), itau_phy, zjulian, dtime, &
42     nhori, nid_hf)
43    
44     CALL histvert(nid_hf, "presnivs", "Vertical levels", "mb", &
45     llm, presnivs/100., nvert)
46    
47     call ini_histhf3d(dtime, presnivs, nid_hf3d)
48     CALL histend(nid_hf)
49    
50     end subroutine ini_histhf
51    
52     !******************************************************************
53    
54     subroutine ini_histhf3d(dtime, presnivs, nid_hf3d)
55    
56     ! From phylmd/ini_histhf3d.h, v 1.2 2005/05/25 13:10:09
57    
58     ! sorties hf 3d
59    
60     use dimens_m, only: iim, jjm, llm
61 guez 6 use dimphy, only: klon, nbtr
62 guez 3 use temps, only: itau_phy, day_ref, annee_ref
63     use clesphys, only: ecrit_hf
64     use phyetat0_m, only: rlon, rlat
65     USE ioipsl, only: ymds2ju, histbeg_totreg, histvert, histend, histdef
66    
67     REAL, intent(in):: dtime ! pas temporel de la physique (s)
68     real, intent(in):: presnivs(:)
69     integer, intent(out):: nid_hf3d
70    
71     real zstohf, zout
72     REAL zx_lon(iim, jjm + 1), zx_lat(iim, jjm + 1)
73     real zjulian
74     integer i, nhori, nvert, idayref
75    
76     !------------------------------------------
77    
78     zstohf = dtime * REAL(ecrit_hf)
79     zout = dtime * REAL(ecrit_hf)
80    
81     idayref = day_ref
82     CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
83    
84     CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), rlon, zx_lon)
85     DO i = 1, iim
86     zx_lon(i, 1) = rlon(i+1)
87     zx_lon(i, (jjm + 1)) = rlon(i+1)
88     ENDDO
89    
90     CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), rlat, zx_lat)
91     CALL histbeg_totreg("histhf3d", iim, zx_lon(:, 1), (jjm + 1), &
92     zx_lat(1, :), 1, iim, 1, (jjm + 1), itau_phy, zjulian, dtime, &
93     nhori, nid_hf3d)
94    
95     CALL histvert(nid_hf3d, "presnivs", "Vertical levels", "mb", &
96     llm, presnivs/100., nvert)
97    
98     ! Champs 3D:
99    
100     CALL histdef(nid_hf3d, "temp", "Air temperature", "K", &
101     iim, (jjm + 1), nhori, llm, 1, llm, nvert, 32, &
102     "ave(X)", zstohf, zout)
103    
104     CALL histdef(nid_hf3d, "ovap", "Specific humidity", "kg/kg", &
105     iim, (jjm + 1), nhori, llm, 1, llm, nvert, 32, &
106     "ave(X)", zstohf, zout)
107    
108     CALL histdef(nid_hf3d, "vitu", "Zonal wind", "m/s", &
109     iim, (jjm + 1), nhori, llm, 1, llm, nvert, 32, &
110     "ave(X)", zstohf, zout)
111    
112     CALL histdef(nid_hf3d, "vitv", "Meridional wind", "m/s", &
113     iim, (jjm + 1), nhori, llm, 1, llm, nvert, 32, &
114     "ave(X)", zstohf, zout)
115    
116 guez 6 if (nbtr >= 3) then
117     CALL histdef(nid_hf3d, "O3", "Ozone mass fraction", "?", iim, &
118     (jjm + 1), nhori, llm, 1, llm, nvert, 32, "ave(X)", zstohf, &
119     zout)
120     end if
121 guez 3
122     CALL histend(nid_hf3d)
123    
124     end subroutine ini_histhf3d
125    
126     !******************************************************************
127    
128     subroutine ini_histday(dtime, presnivs, ok_journe, nid_day)
129    
130     ! From phylmd/ini_histday.h, v 1.3 2005/05/25 13:10:09
131    
132     use dimens_m, only: iim, jjm, llm
133     use dimphy, only: klon
134     use temps, only: itau_phy, day_ref, annee_ref
135     USE ioipsl, only: ymds2ju, histbeg_totreg, histvert, histend
136     use phyetat0_m, only: rlon, rlat
137    
138     REAL, intent(in):: dtime ! pas temporel de la physique (s)
139     real, intent(in):: presnivs(:)
140     logical, intent(in):: ok_journe
141     integer, intent(out):: nid_day
142    
143     REAL zx_lon(iim, jjm + 1), zx_lat(iim, jjm + 1)
144     integer i, nhori, nvert, idayref
145     real zjulian
146    
147     !--------------------------------
148    
149     IF (ok_journe) THEN
150     idayref = day_ref
151     CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
152    
153     CALL gr_fi_ecrit(1, klon, iim, jjm + 1, rlon, zx_lon)
154     DO i = 1, iim
155     zx_lon(i, 1) = rlon(i+1)
156     zx_lon(i, jjm + 1) = rlon(i+1)
157     ENDDO
158     CALL gr_fi_ecrit(1, klon, iim, jjm + 1, rlat, zx_lat)
159     CALL histbeg_totreg("histday", iim, zx_lon(:, 1), jjm + 1, &
160     zx_lat(1, :), 1, iim, 1, jjm + 1, itau_phy, zjulian, dtime, &
161     nhori, nid_day)
162     CALL histvert(nid_day, "presnivs", "Vertical levels", "mb", &
163     llm, presnivs/100., nvert)
164    
165     CALL histend(nid_day)
166     ENDIF ! fin de test sur ok_journe
167    
168     end subroutine ini_histday
169    
170     !****************************************************
171    
172     subroutine ini_histins(dtime, presnivs, ok_instan, nid_ins)
173    
174     ! From phylmd/ini_histins.h, v 1.2 2005/05/25 13:10:09
175    
176     use dimens_m, only: iim, jjm, llm
177     use dimphy, only: klon
178     use temps, only: itau_phy, day_ref, annee_ref
179     use clesphys, only: ecrit_ins
180     use indicesol, only: nbsrf, clnsurf
181     USE ioipsl, only: ymds2ju, histbeg_totreg, histvert, histend, histdef
182     use phyetat0_m, only: rlon, rlat
183    
184     REAL, intent(in):: dtime ! pas temporel de la physique (s)
185     real, intent(in):: presnivs(:)
186     logical, intent(in):: ok_instan
187     integer, intent(out):: nid_ins
188    
189     REAL zx_lon(iim, jjm + 1), zx_lat(iim, jjm + 1)
190     real zjulian, zsto, zout
191     integer i, nhori, nvert, idayref, nsrf
192    
193     !-------------------------------------------------------------------
194    
195     IF (ok_instan) THEN
196    
197     zsto = dtime * ecrit_ins
198     zout = dtime * ecrit_ins
199    
200     idayref = day_ref
201     CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
202    
203     CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), rlon, zx_lon)
204     DO i = 1, iim
205     zx_lon(i, 1) = rlon(i+1)
206     zx_lon(i, (jjm + 1)) = rlon(i+1)
207     ENDDO
208     CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), rlat, zx_lat)
209     CALL histbeg_totreg("histins", iim, zx_lon(:, 1), (jjm + 1), &
210     zx_lat(1, :), 1, iim, 1, (jjm + 1), itau_phy, zjulian, dtime, &
211     nhori, nid_ins)
212     write(*, *)'Inst ', itau_phy, zjulian
213     CALL histvert(nid_ins, "presnivs", "Vertical levels", "mb", &
214     llm, presnivs/100., nvert)
215    
216     CALL histdef(nid_ins, "phis", "Surface geop. height", "-", &
217     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
218     "once", zsto, zout)
219    
220     CALL histdef(nid_ins, "aire", "Grid area", "-", &
221     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
222     "once", zsto, zout)
223    
224     ! Champs 2D:
225    
226     CALL histdef(nid_ins, "tsol", "Surface Temperature", "K", &
227     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
228     "inst(X)", zsto, zout)
229    
230     CALL histdef(nid_ins, "t2m", "Temperature 2m", "K", &
231     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
232     "inst(X)", zsto, zout)
233    
234     CALL histdef(nid_ins, "q2m", "Specific humidity 2m", "Kg/Kg", &
235     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
236     "inst(X)", zsto, zout)
237    
238     CALL histdef(nid_ins, "u10m", "Vent zonal 10m", "m/s", &
239     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
240     "inst(X)", zsto, zout)
241    
242     CALL histdef(nid_ins, "v10m", "Vent meridien 10m", "m/s", &
243     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
244     "inst(X)", zsto, zout)
245    
246     CALL histdef(nid_ins, "psol", "Surface Pressure", "Pa", &
247     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
248     "inst(X)", zsto, zout)
249    
250     CALL histdef(nid_ins, "plul", "Large-scale Precip.", "mm/day", &
251     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
252     "inst(X)", zsto, zout)
253    
254     CALL histdef(nid_ins, "pluc", "Convective Precip.", "mm/day", &
255     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
256     "inst(X)", zsto, zout)
257    
258     CALL histdef(nid_ins, "cdrm", "Momentum drag coef.", "-", &
259     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
260     "inst(X)", zsto, zout)
261    
262     CALL histdef(nid_ins, "cdrh", "Heat drag coef.", "-", &
263     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
264     "inst(X)", zsto, zout)
265    
266     CALL histdef(nid_ins, "precip", "Precipitation Totale liq+sol", &
267     "kg/(s*m2)", &
268     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
269     "inst(X)", zsto, zout)
270    
271     CALL histdef(nid_ins, "snow", "Snow fall", "kg/(s*m2)", &
272     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
273     "inst(X)", zsto, zout)
274    
275     ! CALL histdef(nid_ins, "snow_mass", "Snow Mass", "kg/m2",
276     ! . iim, (jjm + 1), nhori, 1, 1, 1, -99, 32,
277     ! . "inst(X)", zsto, zout)
278    
279     CALL histdef(nid_ins, "topl", "OLR", "W/m2", &
280     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
281     "inst(X)", zsto, zout)
282    
283     CALL histdef(nid_ins, "evap", "Evaporation", "kg/(s*m2)", &
284     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
285     "inst(X)", zsto, zout)
286    
287     CALL histdef(nid_ins, "sols", "Solar rad. at surf.", "W/m2", &
288     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
289     "inst(X)", zsto, zout)
290    
291     CALL histdef(nid_ins, "soll", "IR rad. at surface", "W/m2", &
292     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
293     "inst(X)", zsto, zout)
294    
295     CALL histdef(nid_ins, "solldown", "Down. IR rad. at surface", &
296     "W/m2", iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
297     "inst(X)", zsto, zout)
298    
299     CALL histdef(nid_ins, "bils", "Surf. total heat flux", "W/m2", &
300     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
301     "inst(X)", zsto, zout)
302    
303     CALL histdef(nid_ins, "sens", "Sensible heat flux", "W/m2", &
304     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
305     "inst(X)", zsto, zout)
306    
307     CALL histdef(nid_ins, "fder", "Heat flux derivation", "W/m2", &
308     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
309     "inst(X)", zsto, zout)
310    
311     CALL histdef(nid_ins, "dtsvdfo", "Boundary-layer dTs(o)", "K/s", &
312     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
313     "inst(X)", zsto, zout)
314    
315     CALL histdef(nid_ins, "dtsvdft", "Boundary-layer dTs(t)", "K/s", &
316     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
317     "inst(X)", zsto, zout)
318    
319     CALL histdef(nid_ins, "dtsvdfg", "Boundary-layer dTs(g)", "K/s", &
320     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
321     "inst(X)", zsto, zout)
322    
323     CALL histdef(nid_ins, "dtsvdfi", "Boundary-layer dTs(g)", "K/s", &
324     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
325     "inst(X)", zsto, zout)
326    
327     DO nsrf = 1, nbsrf
328    
329     call histdef(nid_ins, "pourc_"//clnsurf(nsrf), &
330     "% "//clnsurf(nsrf), "%", &
331     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
332     "inst(X)", zsto, zout)
333    
334     call histdef(nid_ins, "fract_"//clnsurf(nsrf), &
335     "Fraction "//clnsurf(nsrf), "1", &
336     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
337     "inst(X)", zsto, zout)
338    
339     call histdef(nid_ins, "sens_"//clnsurf(nsrf), &
340     "Sensible heat flux "//clnsurf(nsrf), "W/m2", &
341     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
342     "inst(X)", zsto, zout)
343    
344     call histdef(nid_ins, "tsol_"//clnsurf(nsrf), &
345     "Surface Temperature"//clnsurf(nsrf), "W/m2", &
346     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
347     "inst(X)", zsto, zout)
348    
349     call histdef(nid_ins, "lat_"//clnsurf(nsrf), &
350     "Latent heat flux "//clnsurf(nsrf), "W/m2", &
351     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
352     "inst(X)", zsto, zout)
353    
354     call histdef(nid_ins, "taux_"//clnsurf(nsrf), &
355     "Zonal wind stress"//clnsurf(nsrf), "Pa", &
356     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
357     "inst(X)", zsto, zout)
358    
359     call histdef(nid_ins, "tauy_"//clnsurf(nsrf), &
360     "Meridional xind stress "//clnsurf(nsrf), "Pa", &
361     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
362     "inst(X)", zsto, zout)
363    
364     call histdef(nid_ins, "albe_"//clnsurf(nsrf), &
365     "Albedo "//clnsurf(nsrf), "-", &
366     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
367     "inst(X)", zsto, zout)
368    
369     call histdef(nid_ins, "rugs_"//clnsurf(nsrf), &
370     "rugosite "//clnsurf(nsrf), "-", &
371     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
372     "inst(X)", zsto, zout)
373     !XXX
374     END DO
375     CALL histdef(nid_ins, "rugs", "rugosity", "-", &
376     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
377     "inst(X)", zsto, zout)
378    
379     CALL histdef(nid_ins, "albs", "Surface albedo", "-", &
380     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
381     "inst(X)", zsto, zout)
382     CALL histdef(nid_ins, "albslw", "Surface albedo LW", "-", &
383     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
384     "inst(X)", zsto, zout)
385    
386     !IM cf. AM 081204 BEG
387     ! HBTM2
388     CALL histdef(nid_ins, "s_pblh", "Boundary Layer Height", "m", &
389     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
390     "inst(X)", zsto, zout)
391    
392     CALL histdef(nid_ins, "s_pblt", "T at Boundary Layer Height", &
393     "K", &
394     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
395     "inst(X)", zsto, zout)
396    
397     CALL histdef(nid_ins, "s_lcl", "Condensation level", "m", &
398     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
399     "inst(X)", zsto, zout)
400    
401     CALL histdef(nid_ins, "s_capCL", "Conv avlbl pot ener for ABL", "J/m2", &
402     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
403     "inst(X)", zsto, zout)
404    
405     CALL histdef(nid_ins, "s_oliqCL", "Liq Water in BL", "kg/m2", &
406     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
407     "inst(X)", zsto, zout)
408    
409     CALL histdef(nid_ins, "s_cteiCL", "Instability criteria (ABL)", "K", &
410     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
411     "inst(X)", zsto, zout)
412    
413     CALL histdef(nid_ins, "s_therm", "Exces du thermique", "K", &
414     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
415     "inst(X)", zsto, zout)
416    
417     CALL histdef(nid_ins, "s_trmb1", "deep_cape(HBTM2)", "J/m2", &
418     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
419     "inst(X)", zsto, zout)
420    
421     CALL histdef(nid_ins, "s_trmb2", "inhibition (HBTM2)", "J/m2", &
422     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
423     "inst(X)", zsto, zout)
424    
425     CALL histdef(nid_ins, "s_trmb3", "Point Omega (HBTM2)", "m", &
426     iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &
427     "inst(X)", zsto, zout)
428    
429     !IM cf. AM 081204 END
430    
431     ! Champs 3D:
432    
433     CALL histdef(nid_ins, "temp", "Temperature", "K", &
434     iim, (jjm + 1), nhori, llm, 1, llm, nvert, 32, &
435     "inst(X)", zsto, zout)
436    
437     CALL histdef(nid_ins, "vitu", "Zonal wind", "m/s", &
438     iim, (jjm + 1), nhori, llm, 1, llm, nvert, 32, &
439     "inst(X)", zsto, zout)
440    
441     CALL histdef(nid_ins, "vitv", "Merid wind", "m/s", &
442     iim, (jjm + 1), nhori, llm, 1, llm, nvert, 32, &
443     "inst(X)", zsto, zout)
444    
445     CALL histdef(nid_ins, "geop", "Geopotential height", "m", &
446     iim, (jjm + 1), nhori, llm, 1, llm, nvert, 32, &
447     "inst(X)", zsto, zout)
448    
449     CALL histdef(nid_ins, "pres", "Air pressure", "Pa", &
450     iim, (jjm + 1), nhori, llm, 1, llm, nvert, 32, &
451     "inst(X)", zsto, zout)
452    
453     CALL histdef(nid_ins, "dtvdf", "Boundary-layer dT", "K/s", &
454     iim, (jjm + 1), nhori, llm, 1, llm, nvert, 32, &
455     "inst(X)", zsto, zout)
456    
457     CALL histdef(nid_ins, "dqvdf", "Boundary-layer dQ", "Kg/Kg/s", &
458     iim, (jjm + 1), nhori, llm, 1, llm, nvert, 32, &
459     "inst(X)", zsto, zout)
460    
461     CALL histend(nid_ins)
462     ENDIF
463    
464     end subroutine ini_histins
465    
466     end module ini_hist

  ViewVC Help
Powered by ViewVC 1.1.21