source: trunk/SRC/ToBeReviewed/CALCULS/norme.pro @ 163

Last change on this file since 163 was 163, checked in by navarro, 18 years ago

header improvements : type of parameters and keywords, default values, spell checking + idldoc assistant (IDL online_help)

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 22.1 KB
Line 
1;------------------------------------------------------------
2;------------------------------------------------------------
3;------------------------------------------------------------
4;+
5;
6; @file_comments
7; calculate the norm of a field of vectors, then make a possible average.
8;   Comment 1: The field of vector can be, 2d:xy, 3d: xyz or xyt,
9; 4d: xyzt
10;   Comment 2:
11; The calculation of the norm is made before the possible spatial or
12; temporal average because the average of the norm is not equal to the
13; norm of averages
14
15;
16; @categories
17; Calculation
18;
19; @param COMPOSANTEU {in}{required}
20; an 2d, 3d or 4d array
21;
22; @param COMPOSANTEV {in}{required}
23; an 2d, 3d or 4d array
24;
25; @keyword BOXZOOM
26; boxzoom on which do the average (by default the domain selected
27; by the last domdef done)
28;
29; @keyword DIREC
30; 't' 'x' 'y' 'z' 'xys' 'xz' 'yz' 'xyz' 'xt' 'yt' 'zt' 'xyt'
31;       'xzt' 'yzt' 'xyzt' Direction on which do averages
32;
33; @returns
34; Array to trace with plt, pltz or pltt.
35;
36; @uses
37; common.pro
38;
39; @restrictions
40; The norm is calculated on points TTo do this calculation, we average
41; field U and Von points T before calculate the norme. At the edge of
42; coast and of domain, we can not calculate fields U and V at points T,
43; that is why these points are at value !values.f_nan.
44;
45; When we calculate on a reduce geographic domain, field U and V have not
46; necessarily the same number of point. In this case, we recut U and V to
47; keep only common points. We profit of this to redo a domdef which redefine
48; a geographic domain on which fields U and V are extracted on same points
49;
50; @restrictions
51; To know what type of array we work with, we  test its size and dates
52; gave by time[0] and time[jpt-1] to know if thee is a temporal dimension.
53; Before to start norme, make sure that time and jpt are defined how
54; they have to!
55;
56; @examples
57; To calculate the average of the norme of streams on all the domain
58; between 0 et 50:
59;      IDL> res=norme(un,vn,boxzoom=[0,50],dir='xyz')
60;
61; @history
62; Sebastien Masson (smasson\@lodyc.jussieu.fr)
63;                       9/6/1999
64;
65; @version
66; $Id$
67;
68;-
69;------------------------------------------------------------
70;------------------------------------------------------------
71;------------------------------------------------------------
72FUNCTION norme, composanteu, composantev, BOXZOOM = boxzoom, DIREC = direc, _extra = ex
73;---------------------------------------------------------
74;
75  compile_opt idl2, strictarrsubs
76;
77@cm_4mesh
78@cm_4data
79@cm_4cal
80  IF NOT keyword_set(key_forgetold) THEN BEGIN
81@updatenew
82@updatekwd
83  ENDIF
84;---------------------------------------------------------
85   tempsun = systime(1)         ; To key_performance
86;
87   IF finite(glamu[0])*finite(gphiu[0])*finite(glamv[0])*finite(gphiv[0]) EQ 0 THEN $
88     return, report(['This version of norme is based on Arakawa C-grid.' $
89                     , 'U and V grids must therefore be defined'])
90;
91;------------------------------------------------------------
92  if keyword_set(boxzoom) then BEGIN
93    Case 1 Of
94      N_Elements(Boxzoom) Eq 1:bte = [lon1, lon2, lat1, lat2, 0., boxzoom[0]]
95      N_Elements(Boxzoom) Eq 2:bte = [lon1, lon2, lat1, lat2, boxzoom[0], boxzoom[1]]
96      N_Elements(Boxzoom) Eq 4:bte = [Boxzoom, vert1, vert2]
97      N_Elements(Boxzoom) Eq 5:bte = [Boxzoom[0:3], 0, Boxzoom[4]]
98      N_Elements(Boxzoom) Eq 6:bte = Boxzoom
99      Else: return, report('Mauvaise Definition de Boxzoom')
100    ENDCASE
101    domdef, boxzoom
102  ENDIF
103;------------------------------------------------------------
104   if NOT keyword_set(direc) then direc = 0
105; construction of u and v at points T
106   u = litchamp(composanteu)
107   v = litchamp(composantev)
108   date1 = time[0]
109   if n_elements(jpt) EQ 0 then date2 = date1 ELSE date2 = time[jpt-1]
110
111   if (size(u))[0] NE (size(v))[0] then return,  -1
112
113   vargrid='T'
114   varname = 'norme '
115   valmask = 1e20
116;
117   grilleu = litchamp(composanteu, /grid)
118   if grilleu EQ '' then grilleu = 'U'
119   grillev = litchamp(composantev, /grid)
120   if grillev EQ '' then grillev = 'V'
121   IF grilleu EQ 'V' AND grillev EQ 'U' THEN inverse = 1
122   IF grilleu EQ 'T' AND grillev EQ 'T' THEN BEGIN
123      interpolle  = 0
124      return, report('cas non code mais facile a faire!')
125   ENDIF ELSE interpolle = 1
126   if keyword_set(inverse) then begin
127      rien = u
128      u = v
129      v = rien
130   endif
131
132
133;------------------------------------------------------------
134; We find common points between u and v
135;------------------------------------------------------------
136   indicexu = (lindgen(jpi))[firstxu:firstxu+nxu-1]
137   indicexv = (lindgen(jpi))[firstxv:firstxv+nxv-1]
138   indicex = inter(indicexu, indicexv)
139   indiceyu = (lindgen(jpj))[firstyu:firstyu+nyu-1]
140   indiceyv = (lindgen(jpj))[firstyv:firstyv+nyv-1]
141   indicey = inter(indiceyu, indiceyv)
142   nx = n_elements(indicex)
143   ny = n_elements(indicey)
144;----------------------------------------------------------------------------
145   case 1 of
146;----------------------------------------------------------------------------
147;----------------------------------------------------------------------------
148;xyz
149;----------------------------------------------------------------------------
150;----------------------------------------------------------------------------
151      (size(u))[0] EQ 3 AND date1 EQ date2 :BEGIN
152;----------------------------------------------------------------------------
153         indice2d = lindgen(jpi, jpj)
154         indice2d = indice2d[indicex[0]:indicex[0]+nx-1,indicey[0]:indicey[0]+ny-1]
155         indice3d = lindgen(jpi, jpj, jpk)
156         indice3d = indice3d[indicex[0]:indicex[0]+nx-1,indicey[0]:indicey[0]+ny-1,firstzt:lastzt]
157;------------------------------------------------------------
158; extraction of u and v on the appropriated domain
159;------------------------------------------------------------
160         case 1 of
161            (size(u))[1] EQ nxu AND (size(u))[2] EQ nyu AND $
162             (size(v))[1] EQ nxv AND (size(v))[2] EQ nyv:BEGIN
163               case (size(u))[3] OF
164                  nzt:BEGIN
165                     if nxu NE nx then $
166                      if indicex[0] EQ firstxu then u = u[0:nx-1,*,*] ELSE u = u[1: nx, *,*]
167                     IF nxv NE nx THEN $
168                      if indicex[0] EQ firstxv then v = v[0:nx-1,*,*] ELSE v = v[1: nx, *,*]
169                     IF nyu NE ny THEN $
170                      if indicey[0] EQ firstyu then u = u[*,0:ny-1,*] ELSE u = u[*, 1: ny,*]
171                     IF nyv NE ny THEN $
172                      if indicey[0] EQ firstyv then v = v[*,0:ny-1,*] ELSE v = v[*, 1: ny,*]
173                  end
174                  jpk:BEGIN
175                     if nxu NE nx then $
176                      if indicex[0] EQ firstxu then u = u[0:nx-1, *,firstzt:lastzt] ELSE u = u[1: nx, *,firstzt:lastzt]
177                     IF nxv NE nx THEN $
178                      if indicex[0] EQ firstxv then v = v[0:nx-1, *,firstzt:lastzt] ELSE v = v[1: nx, *,firstzt:lastzt]
179                     IF nyu NE ny THEN $
180                      if indicey[0] EQ firstyu then u = u[*, 0:ny-1,firstzt:lastzt] ELSE u = u[*, 1: ny,firstzt:lastzt]
181                     IF nyv NE ny THEN $
182                      if indicey[0] EQ firstyv then v = v[*, 0:ny-1,firstzt:lastzt] ELSE v = v[*, 1: ny,firstzt:lastzt]
183                  end
184                  ELSE: return, report('problemes d''adequation entre la taille du domaine et la taille des matrices necessaires a tracer des vecteurs')
185               endcase
186            END
187            (size(u))[1] EQ jpi AND (size(u))[2] EQ jpj AND (size(u))[3] EQ jpk AND $
188             (size(v))[1] EQ jpi AND (size(v))[2] EQ jpj AND (size(u))[3] EQ jpk :BEGIN
189               u = u[indice3d]
190               v = v[indice3d]
191            END
192            ELSE: return, report('problemes d''adequation entre la taille du domaine et la taille des matrices necessaires a tracer des vecteurs')
193         endcase
194;------------------------------------------------------------------
195; We reshape u and v to make sure that no dimension has been erased
196;------------------------------------------------------------------
197         if nzt EQ 1 then begin
198            u = reform(u, nx, ny, nzt, /over)
199            v = reform(v, nx, ny, nzt, /over)
200         endif
201;------------------------------------------------------------------
202; construction of u and v at points T
203;-----------------------------------------------------------
204         a=u[0,*,*]
205         u=(u+shift(u,1,0,0))/2.
206         if NOT keyword_set(key_periodic) OR nx NE jpi then u[0,*,*]=a
207         a=v[*,0,*]
208         v=(v+shift(v,0,1,0))/2.
209         if NOT keyword_set(key_periodic) OR nx NE jpi then v[*,0,*]=a
210;----------------------------------------------------------------------------
211; attribution of the mask and of logitude and latitude arrays
212;----------------------------------------------------------------------------
213         mask = tmask[indice3d]
214         if nzt EQ 1 then mask = reform(mask, nx, ny, nzt, /over)
215;-----------------------------------------------------------
216         if n_elements(valmask) EQ 0 THEN valmask = 1e20
217         landu = where(u GE valmask/10)
218         if landu[0] NE -1 then u[landu] = 0
219         landv = where(v GE valmask/10)
220         if landv[0] NE -1 then v[landv] = 0
221         res=sqrt(u^2+v^2)
222         if NOT keyword_set(key_periodic) OR nx NE jpi then res[0,*, *]=!values.f_nan
223         res[*,0, *]=!values.f_nan
224         mask = where(mask eq 0)
225         IF mask[0] NE -1 THEN res[mask] = valmask
226; All kind of average
227         domdef, (glamt[indice2d])[0, 0], (glamu[indice2d])[nx-1, 0],(gphit[indice2d])[0, 0], (gphiv[indice2d])[0, ny-1], vert1, vert2, /meme
228         if keyword_set(direc) then res = moyenne(res,direc,/nan, boxzoom = boxzoom, /nodomdef)
229;-----------------------------------------------------------
230      END
231;----------------------------------------------------------------------------
232;----------------------------------------------------------------------------
233;xyt
234;----------------------------------------------------------------------------
235;----------------------------------------------------------------------------
236      date1 NE date2 AND (size(u))[0] EQ 3 :BEGIN
237         indice2d = lindgen(jpi, jpj)
238         indice2d = indice2d[indicex[0]:indicex[0]+nx-1,indicey[0]:indicey[0]+ny-1]
239;------------------------------------------------------------
240; extraction of u and v on the appropriated domain
241;------------------------------------------------------------
242         case 1 of
243            (size(u))[1] EQ nxu AND (size(u))[2] EQ nyu AND $
244             (size(v))[1] EQ nxv AND (size(v))[2] EQ nyv:BEGIN
245               if nxu NE nx then $
246                if indicex[0] EQ firstxu then u = u[0:nx-1, *, *] ELSE u = u[1: nx, *, *]
247               IF nxv NE nx THEN $
248                if indicex[0] EQ firstxv then v = v[0:nx-1, *, *] ELSE v = v[1: nx, *, *]
249               IF nyu NE ny THEN $
250                if indicey[0] EQ firstyu then u = u[*, 0:ny-1, *] ELSE u = u[*, 1: ny, *]
251               IF nyv NE ny THEN $
252                if indicey[0] EQ firstyv then v = v[*, 0:ny-1, *] ELSE v = v[*, 1: ny, *]
253            END
254            (size(u))[1] EQ jpi AND (size(u))[2] EQ jpj AND $
255             (size(v))[1] EQ jpi AND (size(v))[2] EQ jpj:BEGIN
256               u = u[indicex[0]:indicex[0]+nx-1,indicey[0]:indicey[0]+ny-1, *]
257               v = v[indicex[0]:indicex[0]+nx-1,indicey[0]:indicey[0]+ny-1, *]
258            END
259            ELSE:return, report('problemes d''adequation entre la taille du domaine et la taille des matrices necessaires a tracer des vecteurs')
260         endcase
261;------------------------------------------------------------------
262; construction of u and v at points T
263;-----------------------------------------------------------
264         a=u[0,*,*]
265         u=(u+shift(u,1,0,0))/2.
266         if NOT keyword_set(key_periodic) OR nx NE jpi then u[0,*,*]=a
267         a=v[*,0,*]
268         v=(v+shift(v,0,1,0))/2.
269         if NOT keyword_set(key_periodic) OR nx NE jpi then v[*,0,*]=a
270;----------------------------------------------------------------------------
271; attribution of the mask and of longitude and latitude arrays.
272; We recover the complete grid to establish a big mask extent in the four
273; direction to cover pointsfor which a land point has been
274; considerated (make a small drawing)
275;----------------------------------------------------------------------------
276         mask = tmask[indice2d+jpi*jpj*firstzt]
277         if ny EQ 1 then mask = reform(mask, nx, ny, /over)
278;-----------------------------------------------------------
279; construction of land containing all points to mask
280;-----------------------------------------------------------
281         if n_elements(valmask) EQ 0 THEN valmask = 1e20
282         landu = where(u GE valmask/10)
283         if landu[0] NE -1 then u[landu] = 0
284         landv = where(v GE valmask/10)
285         if landv[0] NE -1 then v[landv] = 0
286         res=sqrt(u^2+v^2)
287         if NOT keyword_set(key_periodic) OR nx NE jpi then res[0,*, *]=!values.f_nan
288         res[*,0, *]=!values.f_nan
289         mask = where(mask eq 0)
290         IF mask[0] NE -1 THEN BEGIN
291            coeftps = lindgen(jpt)*nx*ny
292            coeftps = replicate(1, n_elements(mask))#coeftps
293            mask = (temporary(mask))[*]#replicate(1, jpt)
294            mask =temporary(mask[*]) + temporary(coeftps[*])
295            res[temporary(mask)] = valmask
296         ENDIF
297; moyennes en tous genres
298         domdef, (glamt[indice2d])[0, 0], (glamu[indice2d])[nx-1, 0],(gphit[indice2d])[0, 0], (gphiv[indice2d])[0, ny-1], vert1, vert2, /meme
299         if keyword_set(direc) then res = grossemoyenne(res,direc,/nan, boxzoom = boxzoom, /nodomdef)
300      END
301;----------------------------------------------------------------------------
302;----------------------------------------------------------------------------
303;xyzt
304;----------------------------------------------------------------------------
305;----------------------------------------------------------------------------
306      date1 NE date2 AND (size(u))[0] EQ 4:BEGIN
307         indice2d = lindgen(jpi, jpj)
308         indice2d = indice2d[indicex[0]:indicex[0]+nx-1,indicey[0]:indicey[0]+ny-1]
309         indice3d = lindgen(jpi, jpj, jpk)
310         indice3d = indice3d[indicex[0]:indicex[0]+nx-1,indicey[0]:indicey[0]+ny-1,firstzt:lastzt]
311;------------------------------------------------------------
312; extraction of u and v on the appropriated domain
313;------------------------------------------------------------
314         case 1 of
315            (size(u))[1] EQ nxu AND (size(u))[2] EQ nyu AND $
316             (size(v))[1] EQ nxv AND (size(v))[2] EQ nyv:BEGIN
317               case (size(u))[3] OF
318                  nzt:BEGIN
319                     if nxu NE nx then $
320                      if indicex[0] EQ firstxu then u = u[0:nx-1,*,*,*] ELSE u = u[1: nx, *,*,*]
321                     IF nxv NE nx THEN $
322                      if indicex[0] EQ firstxv then v = v[0:nx-1,*,*,*] ELSE v = v[1: nx, *,*,*]
323                     IF nyu NE ny THEN $
324                      if indicey[0] EQ firstyu then u = u[*,0:ny-1,*,*] ELSE u = u[*, 1: ny,*,*]
325                     IF nyv NE ny THEN $
326                      if indicey[0] EQ firstyv then v = v[*,0:ny-1,*,*] ELSE v = v[*, 1: ny,*,*]
327                  end
328                  jpk:BEGIN
329                     if nxu NE nx then $
330                      if indicex[0] EQ firstxu then u = u[0:nx-1, *,firstzt:lastzt,*] ELSE u = u[1: nx, *,firstzt:lastzt,*]
331                     IF nxv NE nx THEN $
332                      if indicex[0] EQ firstxv then v = v[0:nx-1, *,firstzt:lastzt,*] ELSE v = v[1: nx, *,firstzt:lastzt,*]
333                     IF nyu NE ny THEN $
334                      if indicey[0] EQ firstyu then u = u[*, 0:ny-1,firstzt:lastzt,*] ELSE u = u[*, 1: ny,firstzt:lastzt,*]
335                     IF nyv NE ny THEN $
336                      if indicey[0] EQ firstyv then v = v[*, 0:ny-1,firstzt:lastzt,*] ELSE v = v[*, 1: ny,firstzt:lastzt,*]
337                  end
338                  ELSE: return, report('problemes d''adequation entre la taille du domaine et la taille des matrices necessaires a tracer des vecteurs')
339               endcase
340            END
341            (size(u))[1] EQ jpi AND (size(u))[2] EQ jpj AND (size(u))[3] EQ jpk AND $
342             (size(v))[1] EQ jpi AND (size(v))[2] EQ jpj AND (size(u))[3] EQ jpk :BEGIN
343               u = u[indicex[0]:indicex[0]+nx-1,indicey[0]:indicey[0]+ny-1,firstzt:lastzt, *]
344               v = v[indicex[0]:indicex[0]+nx-1,indicey[0]:indicey[0]+ny-1,firstzt:lastzt, *]
345            END
346            ELSE: return, report('problemes d''adequation entre la taille du domaine et la taille des matrices necessaires a tracer des vecteurs')
347         endcase
348;------------------------------------------------------------------
349; construction of u and v at points T
350;-----------------------------------------------------------
351         a=u[0,*,*,*]
352         u=(u+shift(u,1,0,0,0))/2.
353         if NOT keyword_set(key_periodic) OR nx NE jpi then u[0,*,*,*]=a
354         a=v[*,0,*,*]
355         v=(v+shift(v,0,1,0,0))/2.
356         if NOT keyword_set(key_periodic) OR nx NE jpi then v[*,0,*,*]=a
357;----------------------------------------------------------------------------
358; attribution of the mask and of logitude and latitude arrays
359;----------------------------------------------------------------------------
360         mask = tmask[indice3d]
361         if nzt EQ 1 then mask = reform(mask, nx, ny, nzt, /over)
362;-----------------------------------------------------------
363         if n_elements(valmask) EQ 0 THEN valmask = 1e20
364         landu = where(u GE valmask/10)
365         if landu[0] NE -1 then u[landu] = 0
366         landv = where(v GE valmask/10)
367         if landv[0] NE -1 then v[landv] = 0
368         res=sqrt(u^2+v^2)
369         if NOT keyword_set(key_periodic) OR nx NE jpi then res[0,*, *, *]=!values.f_nan
370         res[*,0, *, *]=!values.f_nan
371         mask = where(mask eq 0)
372         IF mask[0] NE -1 THEN BEGIN
373            coeftps = lindgen(jpt)*nx*ny*nzt
374            coeftps = replicate(1, n_elements(mask))#coeftps
375            mask = (temporary(mask))[*]#replicate(1, jpt)
376            mask =temporary(mask[*]) + temporary(coeftps[*])
377            res[temporary(mask)] = valmask
378         ENDIF
379; All kind of average
380         domdef, (glamt[indice2d])[0, 0], (glamu[indice2d])[nx-1, 0],(gphit[indice2d])[0, 0], (gphiv[indice2d])[0, ny-1], vert1, vert2, /meme
381         if keyword_set(direc) then res = grossemoyenne(res,direc,/nan, boxzoom = boxzoom, /nodomdef)
382      END
383;----------------------------------------------------------------------------
384;----------------------------------------------------------------------------
385;xy
386;----------------------------------------------------------------------------
387;----------------------------------------------------------------------------
388      ELSE:BEGIN                ;xy
389         indice2d = lindgen(jpi, jpj)
390         indice2d = indice2d[indicex[0]:indicex[0]+nx-1,indicey[0]:indicey[0]+ny-1]
391;------------------------------------------------------------
392; extraction of u and v on the appropriated domain
393;------------------------------------------------------------
394         case 1 of
395            (size(u))[1] EQ nxu AND (size(u))[2] EQ nyu AND $
396             (size(v))[1] EQ nxv AND (size(v))[2] EQ nyv:BEGIN
397               if nxu NE nx then $
398                if indicex[0] EQ firstxu then u = u[0:nx-1, *] ELSE u = u[1: nx, *]
399               IF nxv NE nx THEN $
400                if indicex[0] EQ firstxv then v = v[0:nx-1, *] ELSE v = v[1: nx, *]
401               IF nyu NE ny THEN $
402                if indicey[0] EQ firstyu then u = u[*, 0:ny-1] ELSE u = u[*, 1: ny]
403               IF nyv NE ny THEN $
404                if indicey[0] EQ firstyv then v = v[*, 0:ny-1] ELSE v = v[*, 1: ny]
405            END
406            (size(u))[1] EQ jpi AND (size(u))[2] EQ jpj AND $
407             (size(v))[1] EQ jpi AND (size(v))[2] EQ jpj:BEGIN
408               u = u[indice2d]
409               v = v[indice2d]
410            END
411            ELSE:return, report('problemes d''adequation entre la taille du domaine et la taille des matrices necessaires a tracer des vecteurs')
412         endcase
413;------------------------------------------------------------------
414; We reshape u and v to make sure that no dimension has been erased
415;------------------------------------------------------------------
416         if ny EQ 1 then begin
417            u = reform(u, nx, ny, /over)
418            v = reform(v, nx, ny, /over)
419         endif
420;------------------------------------------------------------------
421; construction of u and v at points T
422;-----------------------------------------------------------
423         a=u[0,*]
424         u=(u+shift(u,1,0))/2.
425         if NOT keyword_set(key_periodic) OR nx NE jpi then u[0,*]=a
426         a=v[*,0]
427         v=(v+shift(v,0,1))/2.
428         if NOT keyword_set(key_periodic) OR nx NE jpi then v[*,0]=a
429;----------------------------------------------------------------------------
430; attribution of the mask and of longitude and latitude arrays.
431; We recover the complete grid to establish a big mask extent in the four
432; direction to cover pointsfor which a land point has been
433; considerated (make a small drawing)
434;----------------------------------------------------------------------------
435         mask = tmask[indice2d+jpi*jpj*firstzt]
436         if nyt EQ 1 THEN mask = reform(mask, nx, ny, /over)
437;-----------------------------------------------------------
438; construction of land containing all points to mask
439;-----------------------------------------------------------
440         if n_elements(valmask) EQ 0 THEN valmask = 1e20
441         landu = where(u GE valmask/10)
442         if landu[0] NE -1 then u[landu] = 0
443         landv = where(v GE valmask/10)
444         if landv[0] NE -1 then v[landv] = 0
445         res=sqrt(u^2+v^2)
446         if NOT keyword_set(key_periodic) OR nx NE jpi then res[0,*]=!values.f_nan
447         res[*,0]=!values.f_nan
448         mask = where(mask eq 0)
449         IF mask[0] NE -1 THEN res[mask] = valmask
450; All kind of average
451         domdef, (glamt[indice2d])[0, 0], (glamu[indice2d])[nx-1, 0],(gphit[indice2d])[0, 0], (gphiv[indice2d])[0, ny-1], vert1, vert2, /meme
452         if keyword_set(direc) then res = moyenne(res,direc,/nan, boxzoom = boxzoom, /nodomdef)
453      END
454;----------------------------------------------------------------------------
455   endcase
456;------------------------------------------------------------
457   if keyword_set(key_performance) THEN print, 'temps norme', systime(1)-tempsun
458   return, res
459end
Note: See TracBrowser for help on using the repository browser.