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

Annotation of /trunk/phylmd/ini_histins.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 335 - (hide annotations)
Thu Sep 12 21:22:46 2019 UTC (4 years, 9 months ago) by guez
File size: 14106 byte(s)
Julian dates be in double precision

`ConfigureCompilerFlags.cmake` and `TAGS.cmake` are now copied into
LMDZE, to avoid dependency on the environment.

Julian dates must be in double precision, to get time step precision.

Add optional attribute to argument sec of procedure ju2ymds. We do
not need sec in procedure dynredem0.

In procedure ju2ymds, by construction, sec cannot be > `un_jour`.

Remove useless intermediary variables in procedure ymds2ju.

1 guez 34 module ini_histins_m
2    
3     implicit none
4    
5 guez 191 integer, save:: nid_ins
6    
7 guez 34 contains
8    
9 guez 298 subroutine ini_histins(ok_newmicro)
10 guez 34
11 guez 213 ! From phylmd/ini_histins.h, version 1.2, 2005/05/25 13:10:09
12 guez 34
13 guez 191 use clesphys, only: ecrit_ins, ok_instan
14 guez 183 use clesphys2, only: conv_emanuel
15 guez 298 use comconst, only: dtphys
16 guez 265 use dimensions, only: iim, jjm, llm, nqmx
17 guez 92 use disvert_m, only: presnivs
18 guez 313 use dynetat0_m, only: rlatu, rlonv
19     use dynetat0_chosen_m, only: day_ref, annee_ref
20 guez 61 USE histbeg_totreg_m, ONLY : histbeg_totreg
21     USE histdef_m, ONLY : histdef
22     USE histend_m, ONLY : histend
23     USE histvert_m, ONLY : histvert
24 guez 92 use indicesol, only: nbsrf, clnsurf
25 guez 321 use infotrac_init_m, only: tname, ttext
26 guez 190 use nr_util, only: pi
27 guez 191 use phyetat0_m, only: itau_phy
28 guez 92 USE ymds2ju_m, only: ymds2ju
29 guez 34
30 guez 217 logical, intent(in):: ok_newmicro
31    
32 guez 175 ! Local:
33 guez 335 double precision julian
34     real zsto, zout
35 guez 190 integer nhori, nvert, nsrf, iq, it
36 guez 34
37     !-------------------------------------------------------------------
38    
39 guez 213 print *, 'Call sequence information: ini_histins'
40    
41 guez 215 test_ok_instan: IF (ok_instan) THEN
42 guez 298 zsto = dtphys * ecrit_ins
43     zout = dtphys * ecrit_ins
44 guez 335 CALL ymds2ju(annee_ref, 1, day_ref, 0.0, julian)
45 guez 190 CALL histbeg_totreg("histins", rlonv(:iim) / pi * 180., &
46     rlatu / pi * 180., 1, iim, &
47 guez 335 1, jjm + 1, itau_phy, julian, dtphys, nhori, nid_ins)
48 guez 213 print *, 'itau_phy = ', itau_phy
49 guez 335 print *, "julian = ", julian
50 guez 34 CALL histvert(nid_ins, "presnivs", "Vertical levels", "mb", &
51 guez 67 presnivs/100., nvert)
52 guez 213
53 guez 306 ! Once:
54 guez 227 CALL histdef(nid_ins, "phis", "surface geopotential", "m2 s-2", &
55 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
56 guez 34 "once", zsto, zout)
57     CALL histdef(nid_ins, "aire", "Grid area", "-", &
58 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
59 guez 34 "once", zsto, zout)
60    
61     ! Champs 2D:
62    
63     CALL histdef(nid_ins, "tsol", "Surface Temperature", "K", &
64 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
65 guez 34 "inst(X)", zsto, zout)
66     CALL histdef(nid_ins, "t2m", "Temperature 2m", "K", &
67 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
68 guez 34 "inst(X)", zsto, zout)
69     CALL histdef(nid_ins, "q2m", "Specific humidity 2m", "Kg/Kg", &
70 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
71 guez 34 "inst(X)", zsto, zout)
72     CALL histdef(nid_ins, "u10m", "Vent zonal 10m", "m/s", &
73 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
74 guez 34 "inst(X)", zsto, zout)
75     CALL histdef(nid_ins, "v10m", "Vent meridien 10m", "m/s", &
76 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
77 guez 34 "inst(X)", zsto, zout)
78     CALL histdef(nid_ins, "psol", "Surface Pressure", "Pa", &
79 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
80 guez 34 "inst(X)", zsto, zout)
81     CALL histdef(nid_ins, "plul", "Large-scale Precip.", "mm/day", &
82 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
83 guez 34 "inst(X)", zsto, zout)
84     CALL histdef(nid_ins, "pluc", "Convective Precip.", "mm/day", &
85 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
86 guez 34 "inst(X)", zsto, zout)
87     CALL histdef(nid_ins, "cdrm", "Momentum drag coef.", "-", &
88 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
89 guez 34 "inst(X)", zsto, zout)
90     CALL histdef(nid_ins, "cdrh", "Heat drag coef.", "-", &
91 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
92 guez 34 "inst(X)", zsto, zout)
93     CALL histdef(nid_ins, "precip", "Precipitation Totale liq+sol", &
94     "kg/(s*m2)", &
95 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
96 guez 34 "inst(X)", zsto, zout)
97     CALL histdef(nid_ins, "snow", "Snow fall", "kg/(s*m2)", &
98 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
99 guez 34 "inst(X)", zsto, zout)
100     CALL histdef(nid_ins, "topl", "OLR", "W/m2", &
101 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
102 guez 34 "inst(X)", zsto, zout)
103     CALL histdef(nid_ins, "evap", "Evaporation", "kg/(s*m2)", &
104 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
105 guez 34 "inst(X)", zsto, zout)
106     CALL histdef(nid_ins, "sols", "Solar rad. at surf.", "W/m2", &
107 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
108 guez 34 "inst(X)", zsto, zout)
109 guez 308 CALL histdef(nid_ins, "rls", "surface net downward longwave flux", &
110     "W/m2", iim, jjm + 1, nhori, 1, 1, 1, -99, "inst(X)", zsto, zout)
111 guez 34 CALL histdef(nid_ins, "solldown", "Down. IR rad. at surface", &
112 guez 306 "W/m2", iim, jjm + 1, nhori, 1, 1, 1, -99, &
113 guez 34 "inst(X)", zsto, zout)
114     CALL histdef(nid_ins, "bils", "Surf. total heat flux", "W/m2", &
115 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
116 guez 34 "inst(X)", zsto, zout)
117     CALL histdef(nid_ins, "sens", "Sensible heat flux", "W/m2", &
118 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
119 guez 34 "inst(X)", zsto, zout)
120     CALL histdef(nid_ins, "fder", "Heat flux derivation", "W/m2", &
121 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
122 guez 34 "inst(X)", zsto, zout)
123     CALL histdef(nid_ins, "dtsvdfo", "Boundary-layer dTs(o)", "K/s", &
124 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
125 guez 34 "inst(X)", zsto, zout)
126     CALL histdef(nid_ins, "dtsvdft", "Boundary-layer dTs(t)", "K/s", &
127 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
128 guez 34 "inst(X)", zsto, zout)
129     CALL histdef(nid_ins, "dtsvdfg", "Boundary-layer dTs(g)", "K/s", &
130 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
131 guez 34 "inst(X)", zsto, zout)
132     CALL histdef(nid_ins, "dtsvdfi", "Boundary-layer dTs(g)", "K/s", &
133 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
134 guez 34 "inst(X)", zsto, zout)
135 guez 215 CALL histdef(nid_ins, "msnow", "surface snow amount", "kg/m2", &
136     iim, jjm + 1, nhori, 1, 1, 1, -99, "inst(X)", zsto, zout)
137 guez 279 CALL histdef(nid_ins, "zxfqcalving", "ice calving", "kg m-2 s-1", &
138     iim, jjm + 1, nhori, 1, 1, 1, -99, "inst(X)", zsto, zout)
139 guez 301 CALL histdef(nid_ins, "run_off_lic", "land ice melt to ocean", &
140     "kg m-2 s-1", iim, jjm + 1, nhori, 1, 1, 1, -99, "inst(X)", zsto, &
141     zout)
142 guez 306 CALL histdef(nid_ins, "flat", "latent heat flux", "W m-2", iim, &
143     jjm + 1, nhori, 1, 1, 1, -99, "inst(X)", zsto, zout)
144 guez 34
145     DO nsrf = 1, nbsrf
146     call histdef(nid_ins, "fract_"//clnsurf(nsrf), &
147     "Fraction "//clnsurf(nsrf), "1", &
148 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
149 guez 34 "inst(X)", zsto, zout)
150     call histdef(nid_ins, "sens_"//clnsurf(nsrf), &
151     "Sensible heat flux "//clnsurf(nsrf), "W/m2", &
152 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
153 guez 34 "inst(X)", zsto, zout)
154     call histdef(nid_ins, "tsol_"//clnsurf(nsrf), &
155     "Surface Temperature"//clnsurf(nsrf), "W/m2", &
156 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
157 guez 34 "inst(X)", zsto, zout)
158     call histdef(nid_ins, "lat_"//clnsurf(nsrf), &
159     "Latent heat flux "//clnsurf(nsrf), "W/m2", &
160 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
161 guez 34 "inst(X)", zsto, zout)
162     call histdef(nid_ins, "taux_"//clnsurf(nsrf), &
163     "Zonal wind stress"//clnsurf(nsrf), "Pa", &
164 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
165 guez 34 "inst(X)", zsto, zout)
166     call histdef(nid_ins, "tauy_"//clnsurf(nsrf), &
167     "Meridional xind stress "//clnsurf(nsrf), "Pa", &
168 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
169 guez 34 "inst(X)", zsto, zout)
170     call histdef(nid_ins, "albe_"//clnsurf(nsrf), &
171     "Albedo "//clnsurf(nsrf), "-", &
172 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
173 guez 34 "inst(X)", zsto, zout)
174     call histdef(nid_ins, "rugs_"//clnsurf(nsrf), &
175     "rugosite "//clnsurf(nsrf), "-", &
176 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
177 guez 34 "inst(X)", zsto, zout)
178 guez 225 call histdef(nid_ins, "u10m_"//clnsurf(nsrf), &
179     "zonal wind 10 m "//clnsurf(nsrf), "m s-1", &
180 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
181 guez 225 "inst(X)", zsto, zout)
182     call histdef(nid_ins, "v10m_"//clnsurf(nsrf), &
183     "meridional wind 10 m "//clnsurf(nsrf), "m s-1", &
184 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
185 guez 225 "inst(X)", zsto, zout)
186 guez 34 END DO
187 guez 206
188 guez 34 CALL histdef(nid_ins, "rugs", "rugosity", "-", &
189 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
190 guez 34 "inst(X)", zsto, zout)
191     CALL histdef(nid_ins, "albs", "Surface albedo", "-", &
192 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
193 guez 34 "inst(X)", zsto, zout)
194     CALL histdef(nid_ins, "s_pblh", "Boundary Layer Height", "m", &
195 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
196 guez 34 "inst(X)", zsto, zout)
197     CALL histdef(nid_ins, "s_pblt", "T at Boundary Layer Height", &
198     "K", &
199 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
200 guez 34 "inst(X)", zsto, zout)
201     CALL histdef(nid_ins, "s_lcl", "Condensation level", "m", &
202 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
203 guez 34 "inst(X)", zsto, zout)
204 guez 259 CALL histdef(nid_ins, "s_capCL", &
205     "Convective available potential energy for atmospheric boundary " &
206 guez 306 // "layer", "J/m2", iim, jjm + 1, nhori, 1, 1, 1, -99, &
207 guez 34 "inst(X)", zsto, zout)
208     CALL histdef(nid_ins, "s_oliqCL", "Liq Water in BL", "kg/m2", &
209 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
210 guez 34 "inst(X)", zsto, zout)
211     CALL histdef(nid_ins, "s_cteiCL", "Instability criteria (ABL)", "K", &
212 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
213 guez 34 "inst(X)", zsto, zout)
214     CALL histdef(nid_ins, "s_therm", "Exces du thermique", "K", &
215 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
216 guez 34 "inst(X)", zsto, zout)
217 guez 221 CALL histdef(nid_ins, "qsurf", "Surface Air humidity", "", &
218 guez 306 iim, jjm + 1, nhori, 1, 1, 1, -99, &
219 guez 221 "inst(X)", zsto, zout)
220 guez 34
221 guez 206 if (conv_emanuel) then
222     CALL histdef(nid_ins, "ptop", "cloud top pressure", &
223     "Pa", iim, jjm + 1, nhori, 1, 1, 1, -99, "inst(X)", zsto, zout)
224     CALL histdef(nid_ins, "dnwd0", "unsaturated downdraft", &
225     "kg/m2/s", iim, jjm + 1, nhori, llm, 1, llm, nvert, "inst(X)", &
226     zsto, zout)
227     end if
228 guez 34
229     ! Champs 3D:
230    
231 guez 212 CALL histdef(nid_ins, "tro3", "ozone mole fraction", "-", &
232     iim, jjm + 1, nhori, llm, 1, llm, nvert, "inst(X)", zsto, zout)
233 guez 34 CALL histdef(nid_ins, "temp", "Temperature", "K", &
234 guez 306 iim, jjm + 1, nhori, llm, 1, llm, nvert, &
235 guez 34 "inst(X)", zsto, zout)
236     CALL histdef(nid_ins, "vitu", "Zonal wind", "m/s", &
237 guez 306 iim, jjm + 1, nhori, llm, 1, llm, nvert, &
238 guez 34 "inst(X)", zsto, zout)
239     CALL histdef(nid_ins, "vitv", "Merid wind", "m/s", &
240 guez 306 iim, jjm + 1, nhori, llm, 1, llm, nvert, &
241 guez 34 "inst(X)", zsto, zout)
242     CALL histdef(nid_ins, "geop", "Geopotential height", "m", &
243 guez 306 iim, jjm + 1, nhori, llm, 1, llm, nvert, &
244 guez 34 "inst(X)", zsto, zout)
245     CALL histdef(nid_ins, "pres", "Air pressure", "Pa", &
246 guez 306 iim, jjm + 1, nhori, llm, 1, llm, nvert, &
247 guez 34 "inst(X)", zsto, zout)
248     CALL histdef(nid_ins, "dtvdf", "Boundary-layer dT", "K/s", &
249 guez 306 iim, jjm + 1, nhori, llm, 1, llm, nvert, &
250 guez 34 "inst(X)", zsto, zout)
251     CALL histdef(nid_ins, "dqvdf", "Boundary-layer dQ", "Kg/Kg/s", &
252 guez 306 iim, jjm + 1, nhori, llm, 1, llm, nvert, &
253 guez 34 "inst(X)", zsto, zout)
254 guez 159 CALL histdef(nid_ins, "zmasse", "column density of air in cell", &
255     "kg m-2", iim, jjm + 1, nhori, llm, 1, llm, nvert, "inst(X)", &
256     zsto, zout)
257 guez 178 CALL histdef(nid_ins, "rhum", "Relative humidity", &
258     "", iim, jjm + 1, nhori, llm, 1, llm, nvert, "inst(X)", &
259     zsto, zout)
260 guez 213 CALL histdef(nid_ins, "d_t_ec", "kinetic dissipation dT", &
261     "K/s", iim, jjm + 1, nhori, llm, 1, llm, nvert, "inst(X)", &
262     zsto, zout)
263     CALL histdef(nid_ins, "dtsw0", "CS SW radiation dT", &
264     "K/s", iim, jjm + 1, nhori, llm, 1, llm, nvert, "inst(X)", &
265     zsto, zout)
266     CALL histdef(nid_ins, "dtlw0", "CS LW radiation dT", &
267     "K/s", iim, jjm + 1, nhori, llm, 1, llm, nvert, "inst(X)", &
268     zsto, zout)
269 guez 326 CALL histdef(nid_ins, "pmflxr", "convective precipitation liquid", "", &
270     iim, jjm + 1, nhori, llm, 1, llm, nvert, "inst(X)", zsto, zout)
271 guez 221
272 guez 217 if (ok_newmicro) then
273     CALL histdef(nid_ins, "re", "cloud droplet effective radius", &
274     "micrometer", iim, jjm + 1, nhori, llm, 1, llm, nvert, &
275     "inst(X)", zsto, zout)
276     CALL histdef(nid_ins, "fl", &
277     "denominator of Cloud droplet effective radius", "", iim, &
278     jjm + 1, nhori, llm, 1, llm, nvert, "inst(X)", zsto, zout)
279     end if
280 guez 178
281 guez 159 DO it = 1, nqmx - 2
282     ! champ 2D
283     iq=it+2
284     CALL histdef(nid_ins, tname(iq), ttext(iq), "U/kga", iim, jjm+1, &
285     nhori, llm, 1, llm, nvert, "inst(X)", zsto, zout)
286     CALL histdef(nid_ins, "fl"//tname(iq), "Flux "//ttext(iq), &
287     "U/m2/s", iim, jjm+1, nhori, llm, 1, llm, nvert, &
288     "inst(X)", zsto, zout)
289     CALL histdef(nid_ins, "d_tr_th_"//tname(iq), &
290     "tendance thermique"// ttext(iq), "?", &
291     iim, jjm+1, nhori, llm, 1, llm, nvert, &
292     "inst(X)", zsto, zout)
293     CALL histdef(nid_ins, "d_tr_cv_"//tname(iq), &
294     "tendance convection"// ttext(iq), "?", &
295     iim, jjm+1, nhori, llm, 1, llm, nvert, &
296     "inst(X)", zsto, zout)
297     CALL histdef(nid_ins, "d_tr_cl_"//tname(iq), &
298     "tendance couche limite"// ttext(iq), "?", &
299     iim, jjm+1, nhori, llm, 1, llm, nvert, &
300     "inst(X)", zsto, zout)
301     ENDDO
302    
303 guez 34 CALL histend(nid_ins)
304 guez 215 ENDIF test_ok_instan
305 guez 34
306     end subroutine ini_histins
307    
308     end module ini_histins_m

  ViewVC Help
Powered by ViewVC 1.1.21