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

Last change on this file was 495, checked in by pinsard, 10 years ago

fix thanks to coding rules; typo; dupe empty lines; trailing blanks

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