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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 61 - (hide annotations)
Fri Apr 20 14:58:43 2012 UTC (12 years, 1 month ago) by guez
File size: 11226 byte(s)
No more included file in LMDZE, not even "netcdf.inc".

Created a variable containing the list of common source files in
GNUmakefile. So we now also see clearly files that are specific to
each program.

Split module "histcom". Assembled resulting files in directory
"Histcom".

Removed aliasing in calls to "laplacien".

1 guez 34 module ini_histins_m
2    
3     implicit none
4    
5     contains
6    
7     subroutine ini_histins(dtime, ok_instan, nid_ins)
8    
9     ! From phylmd/ini_histins.h, v 1.2 2005/05/25 13:10:09
10    
11     use dimens_m, only: iim, jjm, llm
12     use dimphy, only: klon
13     use temps, only: itau_phy, day_ref, annee_ref
14     use clesphys, only: ecrit_ins
15     use indicesol, only: nbsrf, clnsurf
16     USE calendar, only: ymds2ju
17 guez 61 USE histbeg_totreg_m, ONLY : histbeg_totreg
18     USE histdef_m, ONLY : histdef
19     USE histend_m, ONLY : histend
20     USE histvert_m, ONLY : histvert
21 guez 34 use phyetat0_m, only: rlon, rlat
22     use comvert, only: presnivs
23    
24     REAL, intent(in):: dtime ! pas temporel de la physique (s)
25     logical, intent(in):: ok_instan
26     integer, intent(out):: nid_ins
27    
28     REAL zx_lon(iim, jjm + 1), zx_lat(iim, jjm + 1)
29     real zjulian, zsto, zout
30     integer i, nhori, nvert, idayref, nsrf
31    
32     !-------------------------------------------------------------------
33    
34     IF (ok_instan) THEN
35    
36     zsto = dtime * ecrit_ins
37     zout = dtime * ecrit_ins
38    
39     idayref = day_ref
40     CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
41    
42     CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), rlon, zx_lon)
43     DO i = 1, iim
44     zx_lon(i, 1) = rlon(i+1)
45     zx_lon(i, (jjm + 1)) = rlon(i+1)
46     ENDDO
47     CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), rlat, zx_lat)
48     CALL histbeg_totreg("histins", zx_lon(:, 1), zx_lat(1, :), 1, iim, 1, &
49     jjm + 1, itau_phy, zjulian, dtime, nhori, nid_ins)
50     write(*, *)'Inst ', itau_phy, zjulian
51     CALL histvert(nid_ins, "presnivs", "Vertical levels", "mb", &
52     llm, presnivs/100., nvert)
53    
54     CALL histdef(nid_ins, "phis", "Surface geop. height", "-", &
55     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
56     "once", zsto, zout)
57    
58     CALL histdef(nid_ins, "aire", "Grid area", "-", &
59     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
60     "once", zsto, zout)
61    
62     ! Champs 2D:
63    
64     CALL histdef(nid_ins, "tsol", "Surface Temperature", "K", &
65     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
66     "inst(X)", zsto, zout)
67    
68     CALL histdef(nid_ins, "t2m", "Temperature 2m", "K", &
69     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
70     "inst(X)", zsto, zout)
71    
72     CALL histdef(nid_ins, "q2m", "Specific humidity 2m", "Kg/Kg", &
73     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
74     "inst(X)", zsto, zout)
75    
76     CALL histdef(nid_ins, "u10m", "Vent zonal 10m", "m/s", &
77     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
78     "inst(X)", zsto, zout)
79    
80     CALL histdef(nid_ins, "v10m", "Vent meridien 10m", "m/s", &
81     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
82     "inst(X)", zsto, zout)
83    
84     CALL histdef(nid_ins, "psol", "Surface Pressure", "Pa", &
85     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
86     "inst(X)", zsto, zout)
87    
88     CALL histdef(nid_ins, "plul", "Large-scale Precip.", "mm/day", &
89     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
90     "inst(X)", zsto, zout)
91    
92     CALL histdef(nid_ins, "pluc", "Convective Precip.", "mm/day", &
93     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
94     "inst(X)", zsto, zout)
95    
96     CALL histdef(nid_ins, "cdrm", "Momentum drag coef.", "-", &
97     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
98     "inst(X)", zsto, zout)
99    
100     CALL histdef(nid_ins, "cdrh", "Heat drag coef.", "-", &
101     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
102     "inst(X)", zsto, zout)
103    
104     CALL histdef(nid_ins, "precip", "Precipitation Totale liq+sol", &
105     "kg/(s*m2)", &
106     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
107     "inst(X)", zsto, zout)
108    
109     CALL histdef(nid_ins, "snow", "Snow fall", "kg/(s*m2)", &
110     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
111     "inst(X)", zsto, zout)
112    
113     ! CALL histdef(nid_ins, "snow_mass", "Snow Mass", "kg/m2",
114     ! . iim, (jjm + 1), nhori, 1, 1, 1, -99,
115     ! . "inst(X)", zsto, zout)
116    
117     CALL histdef(nid_ins, "topl", "OLR", "W/m2", &
118     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
119     "inst(X)", zsto, zout)
120    
121     CALL histdef(nid_ins, "evap", "Evaporation", "kg/(s*m2)", &
122     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
123     "inst(X)", zsto, zout)
124    
125     CALL histdef(nid_ins, "sols", "Solar rad. at surf.", "W/m2", &
126     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
127     "inst(X)", zsto, zout)
128    
129     CALL histdef(nid_ins, "soll", "IR rad. at surface", "W/m2", &
130     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
131     "inst(X)", zsto, zout)
132    
133     CALL histdef(nid_ins, "solldown", "Down. IR rad. at surface", &
134     "W/m2", iim, (jjm + 1), nhori, 1, 1, 1, -99, &
135     "inst(X)", zsto, zout)
136    
137     CALL histdef(nid_ins, "bils", "Surf. total heat flux", "W/m2", &
138     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
139     "inst(X)", zsto, zout)
140    
141     CALL histdef(nid_ins, "sens", "Sensible heat flux", "W/m2", &
142     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
143     "inst(X)", zsto, zout)
144    
145     CALL histdef(nid_ins, "fder", "Heat flux derivation", "W/m2", &
146     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
147     "inst(X)", zsto, zout)
148    
149     CALL histdef(nid_ins, "dtsvdfo", "Boundary-layer dTs(o)", "K/s", &
150     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
151     "inst(X)", zsto, zout)
152    
153     CALL histdef(nid_ins, "dtsvdft", "Boundary-layer dTs(t)", "K/s", &
154     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
155     "inst(X)", zsto, zout)
156    
157     CALL histdef(nid_ins, "dtsvdfg", "Boundary-layer dTs(g)", "K/s", &
158     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
159     "inst(X)", zsto, zout)
160    
161     CALL histdef(nid_ins, "dtsvdfi", "Boundary-layer dTs(g)", "K/s", &
162     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
163     "inst(X)", zsto, zout)
164    
165     DO nsrf = 1, nbsrf
166    
167     call histdef(nid_ins, "pourc_"//clnsurf(nsrf), &
168     "% "//clnsurf(nsrf), "%", &
169     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
170     "inst(X)", zsto, zout)
171    
172     call histdef(nid_ins, "fract_"//clnsurf(nsrf), &
173     "Fraction "//clnsurf(nsrf), "1", &
174     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
175     "inst(X)", zsto, zout)
176    
177     call histdef(nid_ins, "sens_"//clnsurf(nsrf), &
178     "Sensible heat flux "//clnsurf(nsrf), "W/m2", &
179     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
180     "inst(X)", zsto, zout)
181    
182     call histdef(nid_ins, "tsol_"//clnsurf(nsrf), &
183     "Surface Temperature"//clnsurf(nsrf), "W/m2", &
184     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
185     "inst(X)", zsto, zout)
186    
187     call histdef(nid_ins, "lat_"//clnsurf(nsrf), &
188     "Latent heat flux "//clnsurf(nsrf), "W/m2", &
189     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
190     "inst(X)", zsto, zout)
191    
192     call histdef(nid_ins, "taux_"//clnsurf(nsrf), &
193     "Zonal wind stress"//clnsurf(nsrf), "Pa", &
194     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
195     "inst(X)", zsto, zout)
196    
197     call histdef(nid_ins, "tauy_"//clnsurf(nsrf), &
198     "Meridional xind stress "//clnsurf(nsrf), "Pa", &
199     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
200     "inst(X)", zsto, zout)
201    
202     call histdef(nid_ins, "albe_"//clnsurf(nsrf), &
203     "Albedo "//clnsurf(nsrf), "-", &
204     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
205     "inst(X)", zsto, zout)
206    
207     call histdef(nid_ins, "rugs_"//clnsurf(nsrf), &
208     "rugosite "//clnsurf(nsrf), "-", &
209     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
210     "inst(X)", zsto, zout)
211     !XXX
212     END DO
213     CALL histdef(nid_ins, "rugs", "rugosity", "-", &
214     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
215     "inst(X)", zsto, zout)
216    
217     CALL histdef(nid_ins, "albs", "Surface albedo", "-", &
218     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
219     "inst(X)", zsto, zout)
220     CALL histdef(nid_ins, "albslw", "Surface albedo LW", "-", &
221     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
222     "inst(X)", zsto, zout)
223    
224     !IM cf. AM 081204 BEG
225     ! HBTM2
226     CALL histdef(nid_ins, "s_pblh", "Boundary Layer Height", "m", &
227     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
228     "inst(X)", zsto, zout)
229    
230     CALL histdef(nid_ins, "s_pblt", "T at Boundary Layer Height", &
231     "K", &
232     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
233     "inst(X)", zsto, zout)
234    
235     CALL histdef(nid_ins, "s_lcl", "Condensation level", "m", &
236     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
237     "inst(X)", zsto, zout)
238    
239     CALL histdef(nid_ins, "s_capCL", "Conv avlbl pot ener for ABL", "J/m2", &
240     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
241     "inst(X)", zsto, zout)
242    
243     CALL histdef(nid_ins, "s_oliqCL", "Liq Water in BL", "kg/m2", &
244     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
245     "inst(X)", zsto, zout)
246    
247     CALL histdef(nid_ins, "s_cteiCL", "Instability criteria (ABL)", "K", &
248     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
249     "inst(X)", zsto, zout)
250    
251     CALL histdef(nid_ins, "s_therm", "Exces du thermique", "K", &
252     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
253     "inst(X)", zsto, zout)
254    
255     CALL histdef(nid_ins, "s_trmb1", "deep_cape(HBTM2)", "J/m2", &
256     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
257     "inst(X)", zsto, zout)
258    
259     CALL histdef(nid_ins, "s_trmb2", "inhibition (HBTM2)", "J/m2", &
260     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
261     "inst(X)", zsto, zout)
262    
263     CALL histdef(nid_ins, "s_trmb3", "Point Omega (HBTM2)", "m", &
264     iim, (jjm + 1), nhori, 1, 1, 1, -99, &
265     "inst(X)", zsto, zout)
266    
267     !IM cf. AM 081204 END
268    
269     ! Champs 3D:
270    
271     CALL histdef(nid_ins, "temp", "Temperature", "K", &
272     iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
273     "inst(X)", zsto, zout)
274    
275     CALL histdef(nid_ins, "vitu", "Zonal wind", "m/s", &
276     iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
277     "inst(X)", zsto, zout)
278    
279     CALL histdef(nid_ins, "vitv", "Merid wind", "m/s", &
280     iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
281     "inst(X)", zsto, zout)
282    
283     CALL histdef(nid_ins, "geop", "Geopotential height", "m", &
284     iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
285     "inst(X)", zsto, zout)
286    
287     CALL histdef(nid_ins, "pres", "Air pressure", "Pa", &
288     iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
289     "inst(X)", zsto, zout)
290    
291     CALL histdef(nid_ins, "dtvdf", "Boundary-layer dT", "K/s", &
292     iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
293     "inst(X)", zsto, zout)
294    
295     CALL histdef(nid_ins, "dqvdf", "Boundary-layer dQ", "Kg/Kg/s", &
296     iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
297     "inst(X)", zsto, zout)
298    
299     CALL histend(nid_ins)
300     ENDIF
301    
302     end subroutine ini_histins
303    
304     end module ini_histins_m

  ViewVC Help
Powered by ViewVC 1.1.21