source: trunk/SRC/ToBeReviewed/PLOTS/DESSINE/pltt.pro @ 264

Last change on this file since 264 was 264, checked in by pinsard, 17 years ago

typo in some pro files

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 27.7 KB
Line 
1;+
2;
3; @file_comments
4; Trace hovmoller graphs: xt,yt,zt,t
5;
6; @categories Graphics
7;
8; @param TAB {in}{required}
9; The field whose we want to make the hovmoller map can be 2 kind of thing:
10;       1) An array which can be:
11;          * 3d or 4d: array  'xt','yt','zt','t'. The last component is the time. In this case, the array will
12;            pass in <pro>grossemoyenne</pro> to be averaged and become an 1d or 2d array.
13;          * 2d: If the array is already 2d, it is not modified (beware, lands must
14;            be masked at the value valmask) and nevertheless, type must be specified
15;            to we know of which trace it is about.
16;            To have a correct caption, respecify the extraction zone via BOXZOOM.
17;          * 1d: only for traces of the 't' type. Nevertheless, type must be specified
18;            to we know of which trace it is about.
19;            To have a correct caption, respecify the  extraction zone via BOXZOOM.
20;       2) a structure respecting all criterions specified by <pro>litchamp</pro>
21;          See IDL> xhelp,'litchamp'. The array contained in the structure
22;          respecting criterions of case 1)
23;
24;
25; @param GIVENTYPE
26;
27; @param GIVENMIN
28; valeur minimum que l''on veut prendre en compte dans le trace
29; des contours. Par defaut on prend le min de tableau (sur les pts mer)
30;
31; @param GIVENMAX
32: valeur maximum que l''on veut prendre en compte dans le trace
33; des contours. Par defaut on prend le max de tableau (sur les pts mer)
34;
35; @param DATMIN
36: c''est la borne inf de l''axe temporel. c''est un
37;       longinteger de la forme yyyymmdd (ou bien yymmdd).
38;
39; @param DATMAX
40; c''est la borne max de l''axe temporel. c''est un
41;       longinteger de la forme yyyymmdd (ou bien yymmdd)
42;
43; @keyword BOXZOOM
44; Vector indicating the geographic zone (3d) on which the extraction of the field must
45; be done to do the hovmoeller.
46;  If BOXZOOM has :
47; 1 element : The extraction is made on [lon1, lon2, lat1, lat2, 0.,boxzoom[0]]
48; 2 elements: The extraction is made on [lon1, lon2, lat1, lat2, boxzoom[0],boxzoom[1]]
49; 4 elements: The extraction is made on [Boxzoom, vert1, vert2]
50; 5 elements: The extraction is made on [Boxzoom[0:3], 0, Boxzoom[4]]
51; 6 elements: The extraction is made on Boxzoom
52;
53; Where lon1, lon2,lat1,lat2,vert1,vert2 are global variables defined at the last
54; <pro>domdef</pro> !
55;
56; @keyword CONTINTERVALLE
57; When CONTOUR is activated, it is the value between 2 isolines
58; traced by a trait. So it can be different from the one specified by INTERVALLE which,
59; in this case, does not control colored isolines in color anymore. If there is noone
60; specified min, we choose a contour min which goes well with the specified interval!
61; If this keyword is not specified, we trace 20 isolines from the min to the max.
62;
63; @keyword CONTLABEL {type=integer}
64; When CONTOUR is activated, if n
65; is different of 0, choose the label type corresponding to n cases for
66; the traced by a traitisolines. To specify the type of label of the
67; colored contour, use LABEL
68;
69; @keyword CONTMAX {default=we take the max of the array passed in the keyword CONTOUR (on ocean points)}
70; When CONTOUR is activated, max value we want to consider in the isoline
71; traced by a trait's line.
72;
73; @keyword CONTMIN {default=we take the min of the array passed in the keyword CONTOUR (on ocean points)}
74; When CONTOUR is activated, min value we want to consider in the isoline
75; traced by a trait's line.
76;
77; @keyword CONTNLEVEL {default=20}
78; When  CONTOUR is activated, it is the number of contours
79; traced by a trait for drawing (active if
80; CONTLABEL=0).
81;
82; @keyword CONTOUR
83; If we want to trace contours of a different field than the one
84; whose we have the colored drawing (by example E-P in color and QSR in contours).
85; It must be a field respecting same characteristics than the argument number one of pltt.
86;
87; @keyword ENDPOINTS
88; keyword specifying that we want to make a vertical cut in diagonal. Then coordinated of extremities
89; of these one are defined by the 4 elements of the vector ENDPOINTS: [x1,y1,x2,y2] which are
90; coordinates.
91;
92; @keyword EXCHANGE_XY
93; Allows to invert axes.
94;
95; @keyword FILTER
96; Apply a slippery average of width FILTER
97;
98; @keyword INTERVALLE
99; Value of an interval between two isolines. If there is none specified min,
100; we choose a min contour which goes well with the specified interval!. If this keyword is not
101; specified, we trace 20 isoline from the min to the max. Comment: When CONTOUR is activated,
102; INTERVALLE only specify the interval between 2 colored isolines. To specify the interval
103; between 2 isolines traced by a trait, use CONTINTERVALLE.
104;
105; @keyword INV
106; Invert the color vector used to color the graph
107;               (without use the black, the white and the used palette)
108;
109; @keyword LABEL {type=integer}
110; If n different of 0, it choose the label's type
111; corresponding to cases n. cf <pro>label</pro>
112; Comment: When CONTOUR is activated, it only specify the label's type for colored isolines.
113; For these one traced by a trait, use CONTLABEL.
114;
115; @keyword COL1d
116; --OBSOLETE--Color number when we make a trace 1d by default, 0.It is better to use the
117; keyword COLOR used by plot.
118;
119; @keyword MAXIN
120; to specify the max value we want to plot with a keyword instead of with the
121; input parameter max. If max is defined by both, parameter and keyword, the
122; keyword is retained.
123;
124; @keyword MININ
125; to specify the min value we want to plot with a keyword instead of with the
126; input parameter min. If min is defined by both, parameter and keyword, the
127; keyword is retained.
128;
129; @keyword NLEVEL {default=20}
130; Number of contours to draw. active if
131; LABEL=0 or is not specified.
132;
133; @keyword NOFILL
134; To make just isolines with no filling
135;
136; @keyword CONTNLEVEL {default=20}
137; When CONTOUR is activated, it is the number of contours
138; traced by a trait for drawing (active if
139; CONTLABEL=0).
140;
141; @keyword OV1D
142; Allows to overprint a 1d curve over a precedent 1d drawing.
143;
144; @keyword OVERPLOT
145; To make a plot over an other one.
146; Comment: Contrarily to the use of CONTOUR or VECTEUR, the use of this keyword
147; does not the caption and/or the color bar.
148;
149; @keyword STRICTFILL
150; Activate this keyword to that the filling of contours be
151; precisely done between the min and the max specified letting values inferior at the
152; specified min and values superior at the specified max in white.
153;
154; @keyword STYLE {default=style=0}
155; Contour's style to adopt to draw isolines
156;
157; @keyword STY1D
158; --OBSOLETE--
159; Number of the style used when we make a 1d drawing. We should better use the
160; keyword LINESTYLE which is tho one of the plot. Beware, this keyword is still
161; useful if we want to d bars instead of curves, put sty1d='bar'
162;
163; @keyword TREND_TYPE
164; Modify field by calling <pro>trends</pro>
165;
166; @keyword TYPEIN
167; allows to specify the type of hovmoller we want to do
168;             'xt','yt','zt','t'
169; with help of a keyword rather than the argument type. If the argument and the
170; keyword are specified in the same time, it is the value specified by the
171; keyword which is retained.
172;
173; @keyword _EXTRA
174; Used to pass keywords
175;
176; @uses
177; common.pro
178;
179; @history
180; Sebastien Masson (smasson\@lodyc.jussieu.fr)
181;                       27/5/98
182;                       Jerome Vialard (adapting plt to hovmoller drawing)
183;                       2/7/98
184;                       Sebastien Masson 14/8/98 (continents,barres)
185;                       15/1/98
186; Adaptation for arrays 3 and 4d to the average be done in pltt rather than during the reading.
187;                       Sebastien Masson 14/8/98
188;                       7/1999
189;                       Eric Guilyardi 29/7/99 FILTER, TREND_TYPE,
190;                       REPEAT_C
191;                       Sebastien Masson 08/02/2000 checkfield and
192;                       usetri keyword.
193;
194; @version
195; $Id$
196;
197; @todo
198; seb: definition of parameters, L.426 à 427, L. 492 à 493
199;-
200;
201PRO pltt, tab, giventype, givenmin, givenmax, datmin, datmax, BOXZOOM = boxzoom, CONTOUR = contour $
202          , ENDPOINTS = endpoints, INTERVALLE = intervalle, INV = inv  $
203          , CONTINTERVALLE = contintervalle, LABEL = label, CONTLABEL = contlabel $
204          , STYLE = style, CONTMAX = contmax, CONTMIN = contmin $
205          , NOFILL = nofill, NLEVEL = nlevel, CONTNLEVEL = contnlevel $
206          , COL1D = col1d, STY1D = sty1d, MININ = minin, MAXIN = maxin $
207          , OV1D = ov1d, FILTER = filter, TREND_TYPE = trend_type $
208          , REPEAT_C = repeat_c, TYPEIN = typein, XT = XT, YT = YT, ZT = zt $
209          , TT = tt, STRICTFILL = strictfill, OVERPLOT = overplot $
210          , EXCHANGE_XY = exchange_xy $
211          , _EXTRA = ex
212;
213  compile_opt idl2, strictarrsubs
214;
215@cm_4mesh
216@cm_4data
217@cm_4cal
218  IF NOT keyword_set(key_forgetold) THEN BEGIN
219@updatenew
220@updatekwd
221  ENDIF
222;--------------------------------------------------------------
223;------------------------------------------------------------
224   tempsun = systime(1)         ; For key_performance
225;--------------------------------------------------------------
226; I2) reinitialization. !p.,!x.,!y.
227; Comment: we do not reinitializate when we call back plt in loop to use contour.
228;--------------------------------------------------------------
229   if n_elements(contour) ne 4 AND NOT keyword_set(overplot) $
230    AND NOT keyword_set(ov1d) then reinitplt
231;--------------------------------------------------------------
232; I1) Reading of the field.
233;--------------------------------------------------------------
234   if (keyword_set(boxzoom) OR keyword_set(endpoints)) $
235     AND n_elements(contour) ne 4 THEN BEGIN
236     savedbox = 1b
237     saveboxparam, 'boxparam4pltt.dat'
238   ENDIF
239   if n_elements(giventype) NE 0 then type = giventype
240   if n_elements(givenmin) NE 0 then min = givenmin
241   if n_elements(givenmax) NE 0 then max = givenmax
242   if n_elements(minin) NE 0 then min = minin
243   if n_elements(maxin) NE 0 then max = maxin
244   if keyword_set(typein) then BEGIN
245      if size(type, /type) NE 7 AND size(type, /type) NE 0 then begin
246         if n_elements(min) NE 0 then max = min
247         min = type
248      endif
249      type = typein
250    ENDIF
251;
252   checktypeminmax, 'pltt', TYPE = type, MIN = min, MAX = max $
253     , XT = XT, YT = YT, ZT = zt, TT = tt, ENDPOINTS = endpoints, _extra = ex
254;
255   if keyword_set(endpoints) then begin
256      section, tab, z2d, glam, gphi, ENDPOINTS = endpoints, TYPE = type $
257        , BOXZOOM = boxzoom, DIREC = direc
258      nx = n_elements(glam)
259      ny = nx
260      if strupcase(vargrid) EQ 'W' then begin
261         z = gdepw[firstzw:lastzw]
262         nz = nzw
263      ENDIF ELSE BEGIN
264         z = gdept[firstzt:lastzt]
265         nz = nzt
266      ENDELSE
267   ENDIF ELSE BEGIN
268      z2d = checkfield(tab, 'pltt', TYPE = type, BOXZOOM = boxzoom $
269                       , direc = direc, _extra = ex)
270      if n_elements(z2d) EQ 1 AND z2d[0] EQ -1 then BEGIN
271        IF keyword_set(savedbox) THEN restoreboxparam, 'boxparam4pltt.dat'
272        return
273      endif
274      grille, mask, glam, gphi, gdep, nx, ny, nz, type = type
275   ENDELSE
276;---------------------------------------------------------------
277; Calculation of trend/anomaly following TREND_TYPE
278;---------------------------------------------------------------
279
280   IF NOT keyword_set(trend_type) THEN trend_type = 0
281
282   IF trend_type GT 0 THEN z2d = trends(z2d, trend_type, type)
283
284;---------------------------------------------------------------
285; Filtering of fields in the 't' case.
286;---------------------------------------------------------------
287
288   IF type EQ 't' AND keyword_set(filter) THEN BEGIN
289      ras = report('    Applying a running mean filter of width '+string(filter, format = '(I3)'))
290      z2d = smooth(z2d, filter)
291      z2d[0:filter/2-1] = 0.
292      z2d[(size(z2d))[1]-filter/2-1:(size(z2d))[1]-1] = 0.
293   ENDIF
294
295;---------------------------------------------------------------
296; Repetition of the temporal series
297;---------------------------------------------------------------
298
299   IF NOT keyword_set(repeat_c) THEN repeat_c = 1
300
301   temps = time[0:jpt-1]
302   IF repeat_c GT 1 THEN BEGIN
303      taille=size(z2d)
304      CASE taille[0] OF
305         1: z2d = reform(z2d#replicate(1, repeat_c), taille[1]*repeat_c)
306         2: BEGIN
307            z2d = z2d[*]#replicate(1, repeat_c)
308            z2d = reform(z2d, taille[1], taille[2]*repeat_c, /over)
309         END
310         ELSE:
311      ENDCASE
312      temps = [temps, (lindgen(jpt*(REPEAT_c-1))+1)*(temps[1]-temps[0])+temps[jpt-1]]
313   ENDIF
314
315;---------------------------------------------------------------
316; Selection of graphic's type.
317;---------------------------------------------------------------
318   taille=size(z2d)
319   case taille[0] of
320      2 : typdes='2d'
321      1 : begin
322         z1d=z2d
323         typdes='1d'
324         if keyword_set(OV1D) then begin
325            yy = z2d
326            if n_elements(datmin) NE 0 then tempsmin = date2jul(datmin) $
327            ELSE tempsmin = temps[0]
328; on shift l''axe du temps pour des questions de precision sur les
329; dates du calendier julien en long qui sont passes en float ds les axes
330            xx = temps-tempsmin
331            !x.range=!x.range-tempsmin
332            !x.tickv=!x.tickv-tempsmin
333; We do a false plot to apply these changes!
334            plot,[0], [0],/noerase,xstyle=5, ystyle = 5, title = '', subtitle = '', ytitle = '', xtitle = ''
335            goto, trace1d
336         endif
337      end
338  endcase
339; We build the mask. For that, the table must be masked (automaticaly done at the
340; value valmask if we pass in moyenne or grossemoyenne)
341   nan = total(finite(z2d,/nan)) < 1
342   if n_elements(valmask) EQ 0 then valmask = 1e20
343   if keyword_set(nan) then begin
344      notanum = where(finite(z2d) EQ 0)
345      z2d[notanum] = 0.
346      mask = z2d LT valmask/10.
347      z2d[notanum] = !values.f_nan
348   ENDIF ELSE mask = z2d LT valmask/10.
349;----------------------------------------------------------------------------
350;   determination du mi:min et du ma:max de z2d ainsi que de max: max et
351;    min: min pour le dessin.
352;-----------------------------------------------------------------------------
353; Do we need to do an autoscale ???
354   autoscale = testvar(var = min) EQ testvar(var = max) AND NOT keyword_set(intervalle)
355   determineminmax, z2d, mask, mi, ma, MININ = min, MAXIN = max, nan = nan, INTERVALLE = intervalle, _extra = ex
356   if n_elements(z2d) EQ 1 AND z2d[0] EQ -1 THEN return
357; We do an autoscale if needed.
358   if autoscale then autoscale, min, max, intervalle
359;-----------------------------------------------------------------------------
360;-----------------------------------------------------------------------------
361   if n_elements(contour) ne 4  AND NOT keyword_set(overplot) THEN $
362    placedessin, 'pltt',posfenetre, posbar, contour = contour, direc = direc, type = type, endpoints = endpoints, _extra = ex
363;--------------------------------------------------------------
364;--------------------------------------------------------------
365; 2nd part: drawing
366;--------------------------------------------------------------
367;-----------------------------------------------------------
368;   definition of axis
369;----------------------------------------------------------
370;-----------------------------------------------------------------------------
371; definition of the abscisse and ordinate vectors.
372; The triangulation is defined in order to the drawing be done from the
373; left bottom to the right up. So the matrix have to be shown like this,
374; from which some transpose and reverse
375;-----------------------------------------------------------------------------
376;-----------------------------------------------------------------------------
377; definition of limits of the temporal axis
378;-----------------------------------------------------------------------------
379   case N_PARAMS() OF
380      5 : begin
381         tempsmin = date2jul(datmin)
382         tempsmax = temps[(jpt*repeat_c)-1]
383      end
384      6 : begin
385         tempsmin = date2jul(datmin)
386         tempsmax = date2jul(datmax)
387      end
388      else : begin
389         tempsmin = temps[0]
390         tempsmax = temps[(jpt*repeat_c)-1]
391      end
392   endcase
393;-----------------------------------------------------------------------------
394; on shift l''axe du temps pour des questions de precision sur les
395; dates du calendier julien en long qui sont passes en float ds les axes
396   case typdes of
397      '1d' : begin
398         yy = z1d
399         xx = temps-tempsmin
400      end
401      '2d' : begin
402         case 1 of
403            type eq 'xt' : BEGIN
404               xx = glam[*, 0]
405               yy = temps-tempsmin
406            end
407            type eq 'yt' : begin
408               IF (size(gphi))[0] EQ 1 then yy = gphi ELSE BEGIN
409                 IF keyword_set(key_irregular) THEN BEGIN
410                   cln = (where(gphi EQ max(gphi)))[0]
411                   yy = reform(gphi[cln MOD nx, *])
412                 ENDIF ELSE yy = reform(gphi[0, *])
413               ENDELSE
414               xx = temps-tempsmin
415               z2d = transpose(z2d)
416               mask = transpose(mask)
417            end
418            type eq 'zt' : begin
419               IF size(gdep, /n_dimensions) EQ 2 THEN $
420                  yy = transpose(gdep) ELSE yy = gdep
421               xx = temps-tempsmin
422               z2d = transpose(z2d)
423               mask = transpose(mask)
424            end
425         endcase
426      end
427   endcase
428;--------------------------------------------------------------
429   if NOT keyword_set(overplot) THEN axe, type, tempsmin, tempsmax, _EXTRA = ex ELSE BEGIN
430      if type EQ 'xt' then BEGIN
431         !y.range=!y.range-tempsmin
432         !y.tickv=!y.tickv-tempsmin
433      ENDIF ELSE BEGIN
434         !x.range=!x.range-tempsmin
435         !x.tickv=!x.tickv-tempsmin
436      ENDELSE
437   ENDELSE
438;------------------------------------------------------------
439;------------------------------------------------------------
440; drawing
441;------------------------------------------------------------
442; 2d
443;------------------------------------------------------------
444   if (typdes eq '2d') then begin
445;--------------------------------------------------------------
446; choice of labels
447;-----------------------------------------------------------
448      if keyword_set(intervalle) AND NOT keyword_set(label) then label=1
449      if keyword_set(label) eq 0 then cas=0 else cas=label
450      label, cas, min, max, ncontour, level_z2d, colnumb, NLEVEL = nlevel $
451             , INTERVALLE = intervalle, strictfill = strictfill
452;--------------------------------------------------------------
453; choice of style
454;-----------------------------------------------------------
455      if not keyword_set(style) then style=0
456      style,style,level_z2d,linestyle,thick
457      if keyword_set(inv) then colnumb=reverse(colnumb)
458;----------------------------------------------------------------------
459      nby = n_elements(yy)
460      nbx = n_elements(xx)
461;
462      if keyword_set(nan) then BEGIN
463;         xx = xx#replicate(1, nby) ; We make a 2d array with axes
464;         yy = replicate(1, nbx)#yy
465         masknan = finite(z2d)
466         IF NOT keyword_set(nofill) THEN z2d[where(masknan EQ 0)] = max
467         mask = temporary(mask)*temporary(masknan)
468      ENDIF
469      z2d = remplit(z2d,nite=2+keyword_set(nan), mask = mask, /basique, _extra=ex)
470      if NOT keyword_set(strictfill) then z2d = min > z2d <  max
471      usetri = 0 ; default definition
472      if keyword_set(nan) then BEGIN
473        triangulation = triangule(mask, /basic, coinmonte = coinmontemask $
474                                  , coindescend = coindescendmask)
475        usetri = 1
476      ENDIF ELSE triangulation = -1
477      IF size(gdep, /n_dimensions) EQ 2 THEN BEGIN
478        usetri = 2
479        IF triangulation[0] EQ -1 THEN $
480           triangulation = triangule(mask, /basic, coinmonte = coinmontemask $
481                                     , coindescend = coindescendmask)
482      ENDIF
483;----------------------------------------------------------------------
484      pltbase, z2d, xx, yy, mask, xx, yy, level_z2d, colnumb, contour = contour, /noerase $
485       , c_linestyle=linestyle,c_labels=1-(indgen(n_elements(level_z2d)) MOD 2) $
486       , trichamp = triangulation, trimsk = triangulation, overplot = overplot $
487       , c_thick=thick, performance = key_performance, nofill = nofill, usetri = usetri $
488       , coinmontemask=coinmontemask, coindescendmask=coindescendmask, _extra = ex
489;------------------------------------------------------------
490      if n_elements(contour) eq 4 then BEGIN ; it is the second time I pass in pltt
491         contour = {mietma:[mi, ma], unit:varunit, inter:intervalle} ; I send back the min, the max and the unity
492         return
493      endif
494;------------------------------------------------------------
495      if keyword_set(contour) then BEGIN
496         pourlegende = [1, 1, 1, 1]
497         oldattributs = saveatt()
498         oldcolnumb = colnumb
499         pltt,contour,type, contmin,contmax,CONTOUR=pourlegende, /noerase, USETRI = usetri $
500          ,INTERVALLE=contintervalle,LABEL=contlabel,STYLE=style, ENDPOINTS = endpoints $
501           , NLEVEL = contnlevel, BOXZOOM = boxzoom, STRICTFILL = strictfill, _extra = ex
502         colnumb = oldcolnumb
503         restoreatt, oldattributs
504      endif
505;----------------------------------------------------------------------
506;----------------------------------------------------------------------
507      if keyword_set(overplot) then GOTO, fini
508;------------------------------------------------------------
509; Trace the line of change of date and the equator.
510;------------------------------------------------------------
511      IF key_onearth THEN BEGIN
512        CASE type OF
513          'xt':oplot, [180, 180] - 360*(!x.range[1] LT 180), !y.range
514          'yt':oplot, !x.range, [0, 0]
515          ELSE:
516        ENDCASE
517      ENDIF
518;------------------------------------------------------------
519;  caption + display of these.
520;------------------------------------------------------------
521      legende,mi,ma,type, CONTOUR = pourlegende, DIREC = direc, INTERVALLE = intervalle $
522       , ENDPOINTS = endpoints, _extra = ex
523;
524; we want to draw the time axis with tick length = 1. if we simply
525; use [xy]style=1 then each axis (up and down or left and right) have
526; majorticks with a length of 1 (-> not very nice when xgridstyle=2),
527; same if xticklen=0.5 (not very nice in the middle). => so we draw
528; the top (right) axis by hand using axis.
529;
530      if n_elements(ex) NE 0 then BEGIN
531; pour avoir un cadre de la couleur noire
532        if (where(tag_names(ex) EQ 'COLOR'))[0] NE -1 then ex.COLOR = 0
533      ENDIF
534;
535      plot, [0], [0], /nodata, /noerase, _extra = ex $
536        , xstyle = 1+4*(keyword_set(endpoints) AND type EQ 'xt' AND lat1 NE lat2)+8*(type EQ 'yt' OR type EQ 'zt') $
537        , ystyle = 1+4*(keyword_set(endpoints) AND type EQ 'yt')+8*(type EQ 'xt')
538; call axis for the missing axis.
539      IF type EQ 'xt' AND NOT keyword_set(endpoints) THEN BEGIN
540        if n_elements(ex) NE 0 then $
541          if (where(tag_names(ex) EQ 'YTICKNAME'))[0] NE -1 then $
542          ex.YTICKNAME = replicate(' ', n_elements(ex.YTICKNAME))
543        axis, yaxis = 1, ystyle = 1, yticklen = 0 $
544          , ytickname = replicate(' ', !y.ticks+1), _extra = ex
545      ENDIF
546      IF (type EQ 'yt' OR type EQ 'zt') AND NOT keyword_set(endpoints) THEN BEGIN
547        if n_elements(ex) NE 0 then $
548          if (where(tag_names(ex) EQ 'XTICKNAME'))[0] NE -1 then $
549          ex.XTICKNAME = replicate(' ', n_elements(ex.XTICKNAME))
550       axis, xaxis = 1, xstyle = 1, xticklen = 0 $
551        , xtickname = replicate(' ', !x.ticks+1), _extra = ex
552      ENDIF
553; ajout d'un axe ds le cas ou l'on utilise endpoints
554      if keyword_set(endpoints) then addaxe, endpoints, type, posfenetre, _EXTRA = ex
555;------------------------------------------------------------
556; color bar
557;------------------------------------------------------------
558      colnumb = colnumb[0:ncontour-1-keyword_set(strictfill)]
559      barrecouleur, colnumb, min,  max, (ncontour-keyword_set(strictfill))/2 $
560                    , position = posbar, _extra = ex
561;------------------------------------------------------------
562   endif
563;------------------------------------------------------------
564; 1d
565;------------------------------------------------------------
566trace1d:
567   if (typdes eq '1d') then begin
568      if (not keyword_set(col1d)) then col1d = 0
569      if keyword_set(sty1d) then BEGIN ;if we want to make bars
570         IF strlowcase(strtrim(sty1d)) EQ 'bar' then begin
571            !y.range = [!y.range[0]-(!y.range[1]-!y.range[0])*.05,!y.range[1]]
572            bar_plot, yy, background = (!d.n_colors-1) < 255,  $
573             baselines = replicate(!y.range[0], n_elements(yy)), barnames = ['', ''], $
574             colors    = replicate(col1d, n_elements(yy)), /outline
575            if n_elements(ex) NE 0 then BEGIN
576; To have a black frame
577              if (where(tag_names(ex) EQ 'COLOR'))[0] NE -1 then ex.COLOR = 0
578            ENDIF
579            plot, [0], [0], /nodata, /noerase, _extra = ex
580            GOTO, fini
581         ENDIF
582      ENDIF
583      if NOT keyword_set(ov1d) then BEGIN
584         !y.range=[min-abs(max-min)/50.,max+abs(max-min)/50.]
585         legende,mi,ma,type, DIREC = direc, _extra = ex
586;
587         if keyword_set(exchange_xy) then begin
588            rien = !x
589            !x = !y
590            !y = rien
591            rien = xx
592            xx = yy
593            yy = rien
594         endif
595         plot, xx, yy, color = col1d, linestyle = sty1d, thick = 2 $
596           , title = '', subtitle = '', _extra = ex
597; draw 0 line
598         if keyword_set(exchange_xy) then $
599           oplot, [0, 0], !y.range ELSE oplot, !x.range, [0, 0]
600; we want to draw the axis with the time axis length = 1. if we simply
601; use xstyle=1 then each axis (up and down) have majorticks with a
602; length of 1 (-> not very nice when xgridstyle=2), same if
603; xticklen=0.5 (not very nice in the middle).
604; => so we draw the top axis by hand using axis.
605         if n_elements(ex) NE 0 then BEGIN
606; To have a black frame
607            if (where(tag_names(ex) EQ 'COLOR'))[0] NE -1 then ex.COLOR = 0
608         ENDIF
609         plot, [0], [0], /nodata, /noerase $
610           , xstyle = 1+8*(1-keyword_set(exchange_xy)) $
611           , ystyle = 1+8*keyword_set(exchange_xy), _extra = ex
612; call axis for the missing axis.
613         if n_elements(ex) NE 0 then BEGIN
614; force tickname to blank array
615            if (where(tag_names(ex) EQ 'YTICKNAME'))[0] NE -1 AND keyword_set(exchange_xy) then ex.YTICKNAME = replicate(' ', n_elements(ex.YTICKNAME))
616            if (where(tag_names(ex) EQ 'XTICKNAME'))[0] NE -1 AND NOT keyword_set(exchange_xy) then ex.XTICKNAME = replicate(' ', n_elements(ex.XTICKNAME))
617         ENDIF
618         if keyword_set(exchange_xy) then  axis, yaxis = 1, ystyle = 1 $
619           , yticklen = 0, ytickname = replicate(' ', !y.ticks+1), _extra = ex $
620         ELSE axis, xaxis = 1, xstyle = 1, xticklen = 0 $
621           , xtickname = replicate(' ', !x.ticks+1), _extra = ex
622       ENDIF ELSE oplot, xx, yy, color = col1d, linestyle = sty1d, thick = 2, _extra = ex
623   endif
624fini:
625;------------------------------------------------------------
626; we reput time axis in IDL julian days and not in julian days count from tempsmin
627;------------------------------------------------------------
628   if type EQ 'xt' then BEGIN
629      !y.range=!y.range+tempsmin
630      !y.tickv=!y.tickv+tempsmin
631   ENDIF ELSE BEGIN
632      !x.range=!x.range+tempsmin
633      !x.tickv=!x.tickv+tempsmin
634   ENDELSE
635; We do a false plot to these values are considerated
636   plot, [0], [0], /nodata, /noerase, xstyle = 5, ystyle = 5 $
637     , title = '', subtitle = '', ytitle = '', xtitle = ''
638;------------------------------------------------------------
639;------------------------------------------------------------
640; 3rd part: possible print
641;------------------------------------------------------------
642;------------------------------------------------------------
643   terminedessin, _extra = ex
644   if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4pltt.dat'
645;------------------------------------------------------------
646   if n_elements(key_performance) NE 0 then $
647    IF key_performance EQ 1 THEN print, 'temps pltt', systime(1)-tempsun
648;------------------------------------------------------------
649;------------------------------------------------------------
650;------------------------------------------------------------
651   return
652end
Note: See TracBrowser for help on using the repository browser.