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

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

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 6 by guez, Tue Mar 4 14:00:42 2008 UTC revision 18 by guez, Thu Aug 7 12:29:13 2008 UTC
# Line 37  contains Line 37  contains
37      ENDDO      ENDDO
38    
39      CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), rlat, zx_lat)      CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), rlat, zx_lat)
40      CALL histbeg_totreg("histhf", iim, zx_lon(:, 1), (jjm + 1), &      CALL histbeg_totreg("histhf", zx_lon(:, 1), zx_lat(1, :), 1, iim, 1, &
41           zx_lat(1, :), 1, iim, 1, (jjm + 1), itau_phy, zjulian, dtime,  &           (jjm + 1), itau_phy, zjulian, dtime, nhori, nid_hf)
          nhori, nid_hf)  
42    
43      CALL histvert(nid_hf, "presnivs", "Vertical levels", "mb", &      CALL histvert(nid_hf, "presnivs", "Vertical levels", "mb", &
44           llm, presnivs/100., nvert)           llm, presnivs/100., nvert)
# Line 88  contains Line 87  contains
87      ENDDO      ENDDO
88    
89      CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), rlat, zx_lat)      CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), rlat, zx_lat)
90      CALL histbeg_totreg("histhf3d", iim, zx_lon(:, 1), (jjm + 1), &      CALL histbeg_totreg("histhf3d", zx_lon(:, 1), zx_lat(1, :), 1, iim, 1, &
91           zx_lat(1, :), 1, iim, 1, (jjm + 1), itau_phy, zjulian, dtime,  &           (jjm + 1), itau_phy, zjulian, dtime, nhori, nid_hf3d)
          nhori, nid_hf3d)  
92    
93      CALL histvert(nid_hf3d, "presnivs", "Vertical levels", "mb", &      CALL histvert(nid_hf3d, "presnivs", "Vertical levels", "mb", &
94           llm, presnivs/100., nvert)           llm, presnivs/100., nvert)
# Line 98  contains Line 96  contains
96      ! Champs 3D:      ! Champs 3D:
97    
98      CALL histdef(nid_hf3d, "temp", "Air temperature", "K", &      CALL histdef(nid_hf3d, "temp", "Air temperature", "K", &
99           iim, (jjm + 1), nhori, llm, 1, llm, nvert, 32, &           iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
100           "ave(X)", zstohf, zout)           "ave(X)", zstohf, zout)
101    
102      CALL histdef(nid_hf3d, "ovap", "Specific humidity", "kg/kg", &      CALL histdef(nid_hf3d, "ovap", "Specific humidity", "kg/kg", &
103           iim, (jjm + 1), nhori, llm, 1, llm, nvert, 32, &           iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
104           "ave(X)", zstohf, zout)           "ave(X)", zstohf, zout)
105    
106      CALL histdef(nid_hf3d, "vitu", "Zonal wind", "m/s", &      CALL histdef(nid_hf3d, "vitu", "Zonal wind", "m/s", &
107           iim, (jjm + 1), nhori, llm, 1, llm, nvert, 32, &           iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
108           "ave(X)", zstohf, zout)           "ave(X)", zstohf, zout)
109    
110      CALL histdef(nid_hf3d, "vitv", "Meridional wind", "m/s", &      CALL histdef(nid_hf3d, "vitv", "Meridional wind", "m/s", &
111           iim, (jjm + 1), nhori, llm, 1, llm, nvert, 32, &           iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
112           "ave(X)", zstohf, zout)           "ave(X)", zstohf, zout)
113    
114      if (nbtr >= 3) then      if (nbtr >= 3) then
115         CALL histdef(nid_hf3d, "O3", "Ozone mass fraction", "?", iim, &         CALL histdef(nid_hf3d, "O3", "Ozone mass fraction", "?", iim, &
116              (jjm + 1), nhori, llm, 1, llm, nvert, 32, "ave(X)", zstohf, &              (jjm + 1), nhori, llm, 1, llm, nvert, "ave(X)", zstohf, &
117              zout)              zout)
118      end if      end if
119    
# Line 125  contains Line 123  contains
123    
124    !******************************************************************    !******************************************************************
125    
126    subroutine ini_histday(dtime, presnivs, ok_journe, nid_day)    subroutine ini_histday(dtime, presnivs, ok_journe, nid_day, nq)
127    
128      ! From phylmd/ini_histday.h, v 1.3 2005/05/25 13:10:09      ! From phylmd/ini_histday.h, v 1.3 2005/05/25 13:10:09
129    
130      use dimens_m, only: iim, jjm, llm      use dimens_m, only: iim, jjm, llm
     use dimphy, only: klon  
131      use temps, only: itau_phy, day_ref, annee_ref      use temps, only: itau_phy, day_ref, annee_ref
132      USE ioipsl, only: ymds2ju, histbeg_totreg, histvert, histend      USE ioipsl, only: ymds2ju, histbeg_totreg, histvert, histend, histdef
133      use phyetat0_m, only: rlon, rlat      use phyetat0_m, only: rlon, rlat
134        use clesphys, only: ecrit_day
135        use grid_change, only: gr_phy_write_2d
136    
137      REAL, intent(in):: dtime ! pas temporel de la physique (s)      REAL, intent(in):: dtime ! pas temporel de la physique (s)
138      real, intent(in):: presnivs(:)      real, intent(in):: presnivs(:)
139      logical, intent(in):: ok_journe      logical, intent(in):: ok_journe
140      integer, intent(out):: nid_day      integer, intent(out):: nid_day
141        INTEGER, intent(in):: nq ! nombre de traceurs (y compris vapeur d'eau)
142    
143      REAL zx_lon(iim, jjm + 1), zx_lat(iim, jjm + 1)      ! Variables local to the procedure:
144      integer i, nhori, nvert, idayref      REAL zx_lat(iim, jjm + 1)
145        integer nhori, nvert
146      real zjulian      real zjulian
147    
148      !--------------------------------      !--------------------------------
149    
150      IF (ok_journe) THEN      IF (ok_journe) THEN
151         idayref = day_ref         CALL ymds2ju(annee_ref, 1, day_ref, 0., zjulian)
152         CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)         zx_lat = gr_phy_write_2d(rlat)
153           CALL histbeg_totreg("histday", rlon(2: iim+1), zx_lat(1, :), 1, iim, &
154         CALL gr_fi_ecrit(1, klon, iim, jjm + 1, rlon, zx_lon)              1, jjm + 1, itau_phy, zjulian, dtime, nhori, nid_day)
        DO i = 1, iim  
           zx_lon(i, 1) = rlon(i+1)  
           zx_lon(i, jjm + 1) = rlon(i+1)  
        ENDDO  
        CALL gr_fi_ecrit(1, klon, iim, jjm + 1, rlat, zx_lat)  
        CALL histbeg_totreg("histday", iim, zx_lon(:, 1), jjm + 1, &  
             zx_lat(1, :), 1, iim, 1, jjm + 1, itau_phy, zjulian, dtime,  &  
             nhori, nid_day)  
155         CALL histvert(nid_day, "presnivs", "Vertical levels", "mb", &         CALL histvert(nid_day, "presnivs", "Vertical levels", "mb", &
156              llm, presnivs/100., nvert)              llm, presnivs/100., nvert)
157           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         CALL histend(nid_day)         CALL histend(nid_day)
165      ENDIF                     ! fin de test sur ok_journe      ENDIF
166    
167    end subroutine ini_histday    end subroutine ini_histday
168    
# Line 206  contains Line 205  contains
205            zx_lon(i, (jjm + 1)) = rlon(i+1)            zx_lon(i, (jjm + 1)) = rlon(i+1)
206         ENDDO         ENDDO
207         CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), rlat, zx_lat)         CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), rlat, zx_lat)
208         CALL histbeg_totreg("histins", iim, zx_lon(:, 1), (jjm + 1), &         CALL histbeg_totreg("histins", zx_lon(:, 1), zx_lat(1, :), 1, iim, 1, &
209              zx_lat(1, :), 1, iim, 1, (jjm + 1), itau_phy, zjulian, dtime, &              jjm + 1, itau_phy, zjulian, dtime, nhori, nid_ins)
             nhori, nid_ins)  
210         write(*, *)'Inst ', itau_phy, zjulian         write(*, *)'Inst ', itau_phy, zjulian
211         CALL histvert(nid_ins, "presnivs", "Vertical levels", "mb", &         CALL histvert(nid_ins, "presnivs", "Vertical levels", "mb", &
212              llm, presnivs/100., nvert)              llm, presnivs/100., nvert)
213    
214         CALL histdef(nid_ins, "phis", "Surface geop. height", "-", &         CALL histdef(nid_ins, "phis", "Surface geop. height", "-", &
215              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &              iim, (jjm + 1), nhori, 1, 1, 1, -99, &
216              "once", zsto, zout)              "once", zsto, zout)
217    
218         CALL histdef(nid_ins, "aire", "Grid area", "-", &         CALL histdef(nid_ins, "aire", "Grid area", "-", &
219              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &              iim, (jjm + 1), nhori, 1, 1, 1, -99, &
220              "once", zsto, zout)              "once", zsto, zout)
221    
222         ! Champs 2D:         ! Champs 2D:
223    
224         CALL histdef(nid_ins, "tsol", "Surface Temperature", "K", &         CALL histdef(nid_ins, "tsol", "Surface Temperature", "K", &
225              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32,  &              iim, (jjm + 1), nhori, 1, 1, 1, -99,  &
226              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
227    
228         CALL histdef(nid_ins, "t2m", "Temperature 2m", "K", &         CALL histdef(nid_ins, "t2m", "Temperature 2m", "K", &
229              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &              iim, (jjm + 1), nhori, 1, 1, 1, -99, &
230              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
231    
232         CALL histdef(nid_ins, "q2m", "Specific humidity 2m", "Kg/Kg", &         CALL histdef(nid_ins, "q2m", "Specific humidity 2m", "Kg/Kg", &
233              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &              iim, (jjm + 1), nhori, 1, 1, 1, -99, &
234              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
235    
236         CALL histdef(nid_ins, "u10m", "Vent zonal 10m", "m/s", &         CALL histdef(nid_ins, "u10m", "Vent zonal 10m", "m/s", &
237              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &              iim, (jjm + 1), nhori, 1, 1, 1, -99, &
238              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
239    
240         CALL histdef(nid_ins, "v10m", "Vent meridien 10m", "m/s", &         CALL histdef(nid_ins, "v10m", "Vent meridien 10m", "m/s", &
241              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &              iim, (jjm + 1), nhori, 1, 1, 1, -99, &
242              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
243    
244         CALL histdef(nid_ins, "psol", "Surface Pressure", "Pa", &         CALL histdef(nid_ins, "psol", "Surface Pressure", "Pa", &
245              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &              iim, (jjm + 1), nhori, 1, 1, 1, -99, &
246              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
247    
248         CALL histdef(nid_ins, "plul", "Large-scale Precip.", "mm/day", &         CALL histdef(nid_ins, "plul", "Large-scale Precip.", "mm/day", &
249              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &              iim, (jjm + 1), nhori, 1, 1, 1, -99, &
250              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
251    
252         CALL histdef(nid_ins, "pluc", "Convective Precip.", "mm/day", &         CALL histdef(nid_ins, "pluc", "Convective Precip.", "mm/day", &
253              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &              iim, (jjm + 1), nhori, 1, 1, 1, -99, &
254              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
255    
256         CALL histdef(nid_ins, "cdrm", "Momentum drag coef.", "-", &         CALL histdef(nid_ins, "cdrm", "Momentum drag coef.", "-", &
257              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32,  &              iim, (jjm + 1), nhori, 1, 1, 1, -99,  &
258              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
259    
260         CALL histdef(nid_ins, "cdrh", "Heat drag coef.", "-", &         CALL histdef(nid_ins, "cdrh", "Heat drag coef.", "-", &
261              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32,  &              iim, (jjm + 1), nhori, 1, 1, 1, -99,  &
262              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
263    
264         CALL histdef(nid_ins, "precip", "Precipitation Totale liq+sol",  &         CALL histdef(nid_ins, "precip", "Precipitation Totale liq+sol",  &
265              "kg/(s*m2)", &              "kg/(s*m2)", &
266              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32,  &              iim, (jjm + 1), nhori, 1, 1, 1, -99,  &
267              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
268    
269         CALL histdef(nid_ins, "snow", "Snow fall", "kg/(s*m2)", &         CALL histdef(nid_ins, "snow", "Snow fall", "kg/(s*m2)", &
270              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32,  &              iim, (jjm + 1), nhori, 1, 1, 1, -99,  &
271              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
272    
273         !        CALL histdef(nid_ins, "snow_mass", "Snow Mass", "kg/m2",         !        CALL histdef(nid_ins, "snow_mass", "Snow Mass", "kg/m2",
274         !    .                iim, (jjm + 1), nhori, 1, 1, 1, -99, 32,         !    .                iim, (jjm + 1), nhori, 1, 1, 1, -99,
275         !    .                "inst(X)", zsto, zout)         !    .                "inst(X)", zsto, zout)
276    
277         CALL histdef(nid_ins, "topl", "OLR", "W/m2", &         CALL histdef(nid_ins, "topl", "OLR", "W/m2", &
278              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &              iim, (jjm + 1), nhori, 1, 1, 1, -99, &
279              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
280    
281         CALL histdef(nid_ins, "evap", "Evaporation", "kg/(s*m2)", &         CALL histdef(nid_ins, "evap", "Evaporation", "kg/(s*m2)", &
282              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32,  &              iim, (jjm + 1), nhori, 1, 1, 1, -99,  &
283              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
284    
285         CALL histdef(nid_ins, "sols", "Solar rad. at surf.", "W/m2", &         CALL histdef(nid_ins, "sols", "Solar rad. at surf.", "W/m2", &
286              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32,  &              iim, (jjm + 1), nhori, 1, 1, 1, -99,  &
287              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
288    
289         CALL histdef(nid_ins, "soll", "IR rad. at surface", "W/m2", &         CALL histdef(nid_ins, "soll", "IR rad. at surface", "W/m2", &
290              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32,  &              iim, (jjm + 1), nhori, 1, 1, 1, -99,  &
291              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
292    
293         CALL histdef(nid_ins, "solldown", "Down. IR rad. at surface",  &         CALL histdef(nid_ins, "solldown", "Down. IR rad. at surface",  &
294              "W/m2", iim, (jjm + 1), nhori, 1, 1, 1, -99, 32,  &              "W/m2", iim, (jjm + 1), nhori, 1, 1, 1, -99,  &
295              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
296    
297         CALL histdef(nid_ins, "bils", "Surf. total heat flux", "W/m2", &         CALL histdef(nid_ins, "bils", "Surf. total heat flux", "W/m2", &
298              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32,  &              iim, (jjm + 1), nhori, 1, 1, 1, -99,  &
299              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
300    
301         CALL histdef(nid_ins, "sens", "Sensible heat flux", "W/m2", &         CALL histdef(nid_ins, "sens", "Sensible heat flux", "W/m2", &
302              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32,  &              iim, (jjm + 1), nhori, 1, 1, 1, -99,  &
303              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
304    
305         CALL histdef(nid_ins, "fder", "Heat flux derivation", "W/m2", &         CALL histdef(nid_ins, "fder", "Heat flux derivation", "W/m2", &
306              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32,  &              iim, (jjm + 1), nhori, 1, 1, 1, -99,  &
307              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
308    
309         CALL histdef(nid_ins, "dtsvdfo", "Boundary-layer dTs(o)", "K/s", &         CALL histdef(nid_ins, "dtsvdfo", "Boundary-layer dTs(o)", "K/s", &
310              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32,  &              iim, (jjm + 1), nhori, 1, 1, 1, -99,  &
311              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
312    
313         CALL histdef(nid_ins, "dtsvdft", "Boundary-layer dTs(t)", "K/s", &         CALL histdef(nid_ins, "dtsvdft", "Boundary-layer dTs(t)", "K/s", &
314              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32,  &              iim, (jjm + 1), nhori, 1, 1, 1, -99,  &
315              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
316    
317         CALL histdef(nid_ins, "dtsvdfg", "Boundary-layer dTs(g)", "K/s", &         CALL histdef(nid_ins, "dtsvdfg", "Boundary-layer dTs(g)", "K/s", &
318              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32,  &              iim, (jjm + 1), nhori, 1, 1, 1, -99,  &
319              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
320    
321         CALL histdef(nid_ins, "dtsvdfi", "Boundary-layer dTs(g)", "K/s", &         CALL histdef(nid_ins, "dtsvdfi", "Boundary-layer dTs(g)", "K/s", &
322              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32,  &              iim, (jjm + 1), nhori, 1, 1, 1, -99,  &
323              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
324    
325         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
326    
327            call histdef(nid_ins, "pourc_"//clnsurf(nsrf),  &            call histdef(nid_ins, "pourc_"//clnsurf(nsrf),  &
328                 "% "//clnsurf(nsrf), "%",   &                 "% "//clnsurf(nsrf), "%",   &
329                 iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &                 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
330                 "inst(X)", zsto, zout)                 "inst(X)", zsto, zout)
331    
332            call histdef(nid_ins, "fract_"//clnsurf(nsrf),  &            call histdef(nid_ins, "fract_"//clnsurf(nsrf),  &
333                 "Fraction "//clnsurf(nsrf), "1",   &                 "Fraction "//clnsurf(nsrf), "1",   &
334                 iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &                 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
335                 "inst(X)", zsto, zout)                 "inst(X)", zsto, zout)
336    
337            call histdef(nid_ins, "sens_"//clnsurf(nsrf),  &            call histdef(nid_ins, "sens_"//clnsurf(nsrf),  &
338                 "Sensible heat flux "//clnsurf(nsrf), "W/m2",   &                 "Sensible heat flux "//clnsurf(nsrf), "W/m2",   &
339                 iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &                 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
340                 "inst(X)", zsto, zout)                 "inst(X)", zsto, zout)
341    
342            call histdef(nid_ins, "tsol_"//clnsurf(nsrf),  &            call histdef(nid_ins, "tsol_"//clnsurf(nsrf),  &
343                 "Surface Temperature"//clnsurf(nsrf), "W/m2",   &                 "Surface Temperature"//clnsurf(nsrf), "W/m2",   &
344                 iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &                 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
345                 "inst(X)", zsto, zout)                 "inst(X)", zsto, zout)
346    
347            call histdef(nid_ins, "lat_"//clnsurf(nsrf),  &            call histdef(nid_ins, "lat_"//clnsurf(nsrf),  &
348                 "Latent heat flux "//clnsurf(nsrf), "W/m2",   &                 "Latent heat flux "//clnsurf(nsrf), "W/m2",   &
349                 iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &                 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
350                 "inst(X)", zsto, zout)                 "inst(X)", zsto, zout)
351    
352            call histdef(nid_ins, "taux_"//clnsurf(nsrf),  &            call histdef(nid_ins, "taux_"//clnsurf(nsrf),  &
353                 "Zonal wind stress"//clnsurf(nsrf), "Pa", &                 "Zonal wind stress"//clnsurf(nsrf), "Pa", &
354                 iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &                 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
355                 "inst(X)", zsto, zout)                 "inst(X)", zsto, zout)
356    
357            call histdef(nid_ins, "tauy_"//clnsurf(nsrf),  &            call histdef(nid_ins, "tauy_"//clnsurf(nsrf),  &
358                 "Meridional xind stress "//clnsurf(nsrf), "Pa",   &                 "Meridional xind stress "//clnsurf(nsrf), "Pa",   &
359                 iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &                 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
360                 "inst(X)", zsto, zout)                 "inst(X)", zsto, zout)
361    
362            call histdef(nid_ins, "albe_"//clnsurf(nsrf),  &            call histdef(nid_ins, "albe_"//clnsurf(nsrf),  &
363                 "Albedo "//clnsurf(nsrf), "-",   &                 "Albedo "//clnsurf(nsrf), "-",   &
364                 iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &                 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
365                 "inst(X)", zsto, zout)                 "inst(X)", zsto, zout)
366    
367            call histdef(nid_ins, "rugs_"//clnsurf(nsrf),  &            call histdef(nid_ins, "rugs_"//clnsurf(nsrf),  &
368                 "rugosite "//clnsurf(nsrf), "-",   &                 "rugosite "//clnsurf(nsrf), "-",   &
369                 iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &                 iim, (jjm + 1), nhori, 1, 1, 1, -99, &
370                 "inst(X)", zsto, zout)                 "inst(X)", zsto, zout)
371            !XXX            !XXX
372         END DO         END DO
373         CALL histdef(nid_ins, "rugs", "rugosity", "-", &         CALL histdef(nid_ins, "rugs", "rugosity", "-", &
374              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32,  &              iim, (jjm + 1), nhori, 1, 1, 1, -99,  &
375              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
376    
377         CALL histdef(nid_ins, "albs", "Surface albedo", "-", &         CALL histdef(nid_ins, "albs", "Surface albedo", "-", &
378              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32,  &              iim, (jjm + 1), nhori, 1, 1, 1, -99,  &
379              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
380         CALL histdef(nid_ins, "albslw", "Surface albedo LW", "-", &         CALL histdef(nid_ins, "albslw", "Surface albedo LW", "-", &
381              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32,  &              iim, (jjm + 1), nhori, 1, 1, 1, -99,  &
382              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
383    
384         !IM cf. AM 081204 BEG         !IM cf. AM 081204 BEG
385         ! HBTM2         ! HBTM2
386         CALL histdef(nid_ins, "s_pblh", "Boundary Layer Height", "m", &         CALL histdef(nid_ins, "s_pblh", "Boundary Layer Height", "m", &
387              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &              iim, (jjm + 1), nhori, 1, 1, 1, -99, &
388              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
389    
390         CALL histdef(nid_ins, "s_pblt", "T at Boundary Layer Height",  &         CALL histdef(nid_ins, "s_pblt", "T at Boundary Layer Height",  &
391              "K", &              "K", &
392              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &              iim, (jjm + 1), nhori, 1, 1, 1, -99, &
393              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
394    
395         CALL histdef(nid_ins, "s_lcl", "Condensation level", "m", &         CALL histdef(nid_ins, "s_lcl", "Condensation level", "m", &
396              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &              iim, (jjm + 1), nhori, 1, 1, 1, -99, &
397              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
398    
399         CALL histdef(nid_ins, "s_capCL", "Conv avlbl pot ener for ABL", "J/m2", &         CALL histdef(nid_ins, "s_capCL", "Conv avlbl pot ener for ABL", "J/m2", &
400              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &              iim, (jjm + 1), nhori, 1, 1, 1, -99, &
401              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
402    
403         CALL histdef(nid_ins, "s_oliqCL", "Liq Water in BL", "kg/m2", &         CALL histdef(nid_ins, "s_oliqCL", "Liq Water in BL", "kg/m2", &
404              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &              iim, (jjm + 1), nhori, 1, 1, 1, -99, &
405              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
406    
407         CALL histdef(nid_ins, "s_cteiCL", "Instability criteria (ABL)", "K", &         CALL histdef(nid_ins, "s_cteiCL", "Instability criteria (ABL)", "K", &
408              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &              iim, (jjm + 1), nhori, 1, 1, 1, -99, &
409              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
410    
411         CALL histdef(nid_ins, "s_therm", "Exces du thermique", "K", &         CALL histdef(nid_ins, "s_therm", "Exces du thermique", "K", &
412              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &              iim, (jjm + 1), nhori, 1, 1, 1, -99, &
413              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
414    
415         CALL histdef(nid_ins, "s_trmb1", "deep_cape(HBTM2)", "J/m2", &         CALL histdef(nid_ins, "s_trmb1", "deep_cape(HBTM2)", "J/m2", &
416              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &              iim, (jjm + 1), nhori, 1, 1, 1, -99, &
417              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
418    
419         CALL histdef(nid_ins, "s_trmb2", "inhibition (HBTM2)", "J/m2", &         CALL histdef(nid_ins, "s_trmb2", "inhibition (HBTM2)", "J/m2", &
420              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &              iim, (jjm + 1), nhori, 1, 1, 1, -99, &
421              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
422    
423         CALL histdef(nid_ins, "s_trmb3", "Point Omega (HBTM2)", "m", &         CALL histdef(nid_ins, "s_trmb3", "Point Omega (HBTM2)", "m", &
424              iim, (jjm + 1), nhori, 1, 1, 1, -99, 32, &              iim, (jjm + 1), nhori, 1, 1, 1, -99, &
425              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
426    
427         !IM cf. AM 081204 END         !IM cf. AM 081204 END
# Line 431  contains Line 429  contains
429         ! Champs 3D:         ! Champs 3D:
430    
431         CALL histdef(nid_ins, "temp", "Temperature", "K", &         CALL histdef(nid_ins, "temp", "Temperature", "K", &
432              iim, (jjm + 1), nhori, llm, 1, llm, nvert, 32, &              iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
433              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
434    
435         CALL histdef(nid_ins, "vitu", "Zonal wind", "m/s", &         CALL histdef(nid_ins, "vitu", "Zonal wind", "m/s", &
436              iim, (jjm + 1), nhori, llm, 1, llm, nvert, 32, &              iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
437              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
438    
439         CALL histdef(nid_ins, "vitv", "Merid wind", "m/s", &         CALL histdef(nid_ins, "vitv", "Merid wind", "m/s", &
440              iim, (jjm + 1), nhori, llm, 1, llm, nvert, 32, &              iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
441              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
442    
443         CALL histdef(nid_ins, "geop", "Geopotential height", "m", &         CALL histdef(nid_ins, "geop", "Geopotential height", "m", &
444              iim, (jjm + 1), nhori, llm, 1, llm, nvert, 32, &              iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
445              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
446    
447         CALL histdef(nid_ins, "pres", "Air pressure", "Pa", &         CALL histdef(nid_ins, "pres", "Air pressure", "Pa", &
448              iim, (jjm + 1), nhori, llm, 1, llm, nvert, 32, &              iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
449              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
450    
451         CALL histdef(nid_ins, "dtvdf", "Boundary-layer dT", "K/s", &         CALL histdef(nid_ins, "dtvdf", "Boundary-layer dT", "K/s", &
452              iim, (jjm + 1), nhori, llm, 1, llm, nvert, 32, &              iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
453              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
454    
455         CALL histdef(nid_ins, "dqvdf", "Boundary-layer dQ", "Kg/Kg/s", &         CALL histdef(nid_ins, "dqvdf", "Boundary-layer dQ", "Kg/Kg/s", &
456              iim, (jjm + 1), nhori, llm, 1, llm, nvert, 32, &              iim, (jjm + 1), nhori, llm, 1, llm, nvert, &
457              "inst(X)", zsto, zout)              "inst(X)", zsto, zout)
458    
459         CALL histend(nid_ins)         CALL histend(nid_ins)
# Line 463  contains Line 461  contains
461    
462    end subroutine ini_histins    end subroutine ini_histins
463    
464      !*************************************************
465    
466      subroutine ini_histrac(nid_tra, pdtphys, presnivs, nq_phys, lessivage)
467    
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        use iniadvtrac_m, only: niadv, tnom, ttext
474        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    
479        INTEGER, intent(out):: nid_tra
480        real, intent(in):: pdtphys  ! pas d'integration pour la physique (s)
481        REAL, intent(in):: presnivs(:)
482    
483        integer, intent(in):: nq_phys
484        ! (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        DO it = 1, nq_phys
519           ! 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  end module ini_hist  end module ini_hist

Legend:
Removed from v.6  
changed lines
  Added in v.18

  ViewVC Help
Powered by ViewVC 1.1.21