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

  ViewVC Help
Powered by ViewVC 1.1.21