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