source: trunk/SRC/Colors/xlct.pro @ 262

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

corrections of some headers and parameters and keywords case. change of pro2href to replace proidl

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 20.0 KB
Line 
1;+
2;
3; @hidden
4;
5;-
6;
7PRO xlct_psave                  ;Save/Restore our plotting state.
8;  Swaps our state with the current state each time its called.
9;
10  compile_opt idl2, strictarrsubs
11;
12
13COMMON xlct_com, r0, g0, b0, tfun, state, filename, cps, psave, pnt, $
14        top, bot, silent, chop, lock, g_lbl, vbot, vtop, g_slider, $
15        gamma, color, use_values, ncolors, cbot, siz, w_height, show_win, $
16        updt_callback, updt_cb_data
17
18tmp = { xlct_psave, win: !d.window, x: !x.s, y: !y.s , xtype: !x.type, $
19                         ytype: !y.type, clip: !p.clip }
20
21wset, psave.win
22!x.type = psave.xtype
23!y.type = psave.ytype
24!x.s = psave.x
25!y.s = psave.y
26!p.clip = psave.clip
27psave = tmp
28end
29
30;+
31; @hidden
32;-
33pro xlct_alert_caller
34;
35  compile_opt idl2, strictarrsubs
36;
37COMMON xlct_com, r0, g0, b0, tfun, state, filename, cps, psave, pnt, $
38        top, bot, silent, chop, lock, g_lbl, vbot, vtop, g_slider, $
39        gamma, color, use_values, ncolors, cbot, siz, w_height, show_win, $
40        updt_callback, p_updt_cb_data
41
42    ErrorStatus = 0
43    CATCH, ErrorStatus
44    if (ErrorStatus NE 0) then begin
45        CATCH, /CANCEL
46        v = DIALOG_MESSAGE(['Unexpected error in XLCT:', $
47                        '!ERR_STRING = ' + !ERR_STRING], $
48                        /ERROR)
49        return
50    endif
51    if (STRLEN(updt_callback) gt 0) then begin
52        if (PTR_VALID(p_updt_cb_data)) then begin
53            CALL_PROCEDURE, updt_callback, DATA=*(p_updt_cb_data)
54        endif else begin
55            CALL_PROCEDURE, updt_callback
56        endelse
57    endif
58end
59
60
61; Redraw the ramp image.
62;+
63; @hidden
64;-
65PRO xlct_show
66;
67  compile_opt idl2, strictarrsubs
68;
69COMMON xlct_com, r0, g0, b0, tfun, state, filename, cps, psave, pnt, $
70        top, bot, silent, chop, lock, g_lbl, vbot, vtop, g_slider, $
71        gamma, color, use_values, ncolors, cbot, siz, w_height, show_win, $
72        updt_callback, p_updt_cb_data
73
74    cur_win = !D.WINDOW
75    WSET, show_win
76    TV, BYTE((FLOAT(ncolors)*FINDGEN(siz)/FLOAT(siz-1)) # $
77        REPLICATE(1, w_height)) + BYTE(cbot)
78
79    WSET, cur_win
80
81    ; Let the caller of XLCT know that the color table was modified
82    xlct_alert_caller
83END
84
85;+
86; @hidden
87; @param i
88; ???
89; @param c
90; ???
91;-
92PRO xlct_draw_cps, i, c
93;
94  compile_opt idl2, strictarrsubs
95;
96COMMON colors, r_orig, g_orig, b_orig, r_curr, g_curr, b_curr
97COMMON xlct_com, r0, g0, b0, tfun, state, filename, cps, psave, pnt, $
98        top, bot, silent, chop, lock, g_lbl, vbot, vtop, g_slider, $
99        gamma, color, use_values, ncolors, cbot
100
101tc = color
102if n_elements(c) gt 0 then begin
103        tc = c
104        if c ne 0 then color = c
105        endif
106
107if i[0] eq -1 then j = indgen(n_elements(cps)) else j = i
108
109plots, cps[j], tfun[j], /noclip, color = tc
110plots, cps[j], tfun[j], /noclip, psym=6, color = tc
111end
112
113;+
114; @hidden
115; @keyword UPDATE
116; ???
117;-
118PRO xlct_transfer, UPDATE=update
119;
120  compile_opt idl2, strictarrsubs
121;
122COMMON colors, r_orig, g_orig, b_orig, r_curr, g_curr, b_curr
123COMMON xlct_com, r0, g0, b0, tfun, state, filename, cps, psave, pnt, $
124        top, bot, silent, chop, lock, g_lbl, vbot, vtop, g_slider, $
125        gamma, color, use_values, ncolors, cbot
126
127l = lonarr(ncolors)             ;Subscripts
128m = n_elements(cps)
129for i=0, m-2 do begin
130        n = cps[i+1]-cps[i]             ;Interval
131        b = (tfun[i+1]-tfun[i])/float(n)
132        l[cps[i]] = findgen(n) * b + (tfun[i] + cbot)
133        endfor
134l[ncolors-1] = tfun[m-1]                ;Last point
135if use_values then begin
136  r_curr[cbot] = (r = l[r_orig])
137  g_curr[cbot] = (g = l[g_orig])
138  b_curr[cbot] = (b = l[b_orig])
139endif else begin
140  r_curr[cbot] = (r = r_orig[l])
141  g_curr[cbot] = (g = g_orig[l])
142  b_curr[cbot] = (b = b_orig[l])
143endelse
144
145tvlct, r,g,b, cbot
146if (keyword_set( update )) then $
147  xlct_show
148end
149
150;+
151; @hidden
152; @param event
153; ???
154;-
155PRO xlct_event, event
156;
157  compile_opt idl2, strictarrsubs
158;
159COMMON colors, r_orig, g_orig, b_orig, r_curr, g_curr, b_curr
160COMMON xlct_com, r0, g0, b0, tfun, state, filename, cps, psave, pnt, $
161        top, bot, silent, chop, lock, g_lbl, vbot, vtop, g_slider, $
162        gamma, color, use_values, ncolors, cbot, siz, w_height, show_win, $
163        updt_callback, p_updt_cb_data
164
165
166IF event.id eq state.draw THEN BEGIN    ;** PROCESS DRAWABLE EVENTS **
167        if event.press ne 0 then begin          ;Pressed button?
168                dmin = 1.0e8            ;Find closest control pnt
169                xlct_psave              ;Remove old
170                p = convert_coord(event.x, event.y, /TO_DATA, /DEVICE)
171                xlct_psave              ;Restore old
172                x = fix(p[0])
173                y = fix(p[1])
174                for i=0, n_elements(cps)-1 do begin
175                        d = (p[0]-cps[i])^2 + (p[1]-tfun[i])^2  ; dist ^ 2
176                        if d lt dmin then begin
177                                dmin = d
178                                pnt = i
179                                endif
180                        endfor
181                return
182                endif
183        if event.release ne 0 then begin        ;Released button?
184                pnt = -1
185                xlct_transfer, /update
186                return
187                endif
188        if pnt lt 0 then return                 ;Don't care here...
189
190        xlct_psave                              ;Remove old
191        ; For visuals with static colormaps, erase plot before drawing new
192        if ((COLORMAP_APPLICABLE(redrawRequired) GT 0) and $
193            (redrawRequired GT 0)) then begin
194           ERASE, color=0
195        endif
196        p = convert_coord(event.x, event.y, /TO_DATA, /DEVICE)  ;Coord of mouse
197        n = ncolors -1          ;Into range....
198        m = n_elements(cps)-1
199        x = fix(p[0]) > 0 < n
200        if pnt eq 0 then x = 0 else $           ;1st & last are fixed
201        if pnt eq m then x = n else $
202        x = x > (cps[pnt-1] + 1) < (cps[pnt+1]-1)  ;Others must be between
203
204        if pnt eq 0 then xlct_draw_cps, [0, 1],0 $  ;Erase old segment
205        else if pnt eq m then xlct_draw_cps, [m-1, m],0 $
206        else xlct_draw_cps, [pnt-1, pnt, pnt+1],0
207        cps[pnt] = x
208        tfun[pnt] = fix(p[1]) > 0 < n
209        xlct_transfer
210
211        b = r_curr * .3 + g_curr * .586 + b_curr * .114 ;Ntsc colors
212        c = max(abs(b-b[cbot]), j)  ; *** J is color index furthest from 0
213
214        if pnt eq 0 then xlct_draw_cps, [0, 1], j $
215        else if pnt eq m then xlct_draw_cps, [m-1, m], j $
216        else xlct_draw_cps, [pnt-1, pnt, pnt+1], j
217
218        xlct_psave              ;Remove old
219        return
220        ENDIF
221
222WIDGET_CONTROL, event.id, GET_UVALUE = eventval
223
224abstop = NCOLORS -1
225
226if event.id eq state.name_list then begin
227        LOADCT, silent=silent, event.index, FILE=filename, NCOLORS=ncolors, $
228                BOTTOM=cbot
229        goto, set_gamma
230        ENDIF
231
232CASE eventval OF
233    "TOP":    BEGIN
234                WIDGET_CONTROL, top, GET_VALUE = vtop
235                if lock ne 0 then begin
236                        vbot = (vtop - lock) > 0 < 100
237                        widget_control, bot, SET_VALUE=vbot
238                        endif
239                GOTO, set_gamma
240              END
241
242    "BOTTOM": BEGIN
243                WIDGET_CONTROL, bot, GET_value = vbot
244                if lock ne 0 then begin
245                        vtop = (vbot + lock) > 0 < 100
246                        widget_control, top, SET_VALUE=vtop
247                        ENDIF
248   set_gamma:
249        if use_values then nc = 256 else nc = ncolors
250        s = (nc-1)/100.
251        x0 = vbot * s
252        x1 = vtop * s
253        if x0 ne x1 then s = (nc-1.0)/(x1 - x0) else s = 1.0
254        int = -s * x0
255        if gamma eq 1.0 then s = round(findgen(nc) * s + int > 0.0) $
256        else s = ((findgen(nc) * (s/nc) + (int/nc) > 0.0) ^ gamma) * nc
257        if chop ne 0 then begin
258            too_high = where(s ge nc, n)
259            if n gt 0 then s[too_high] = 0L
260            endif
261        if use_values then begin
262            s = s < 255L
263            l = lindgen(ncolors) + cbot
264            r_curr[cbot] = (r = s[r_orig[l]])
265            g_curr[cbot] = (g = s[g_orig[l]])
266            b_curr[cbot] = (b = s[b_orig[l]])
267        endif else begin
268            s = s + cbot
269            r_curr[cbot] = (r = r_orig[s])
270            g_curr[cbot] = (g = g_orig[s])
271            b_curr[cbot] = (b = b_orig[s])
272        endelse
273        tvlct, r,g,b, cbot
274        xlct_show
275        ENDCASE
276
277    "GAMMA": BEGIN
278                WIDGET_CONTROL, g_slider, GET_VALUE = gamma
279                gamma = 10^((gamma/50.) - 1)
280                WIDGET_CONTROL, g_lbl, SET_VALUE = $
281                        STRING(gamma, format='(f6.3)')
282                goto, set_gamma
283             ENDCASE
284
285    "GANG" : IF event.value eq 0 then lock = 0 else lock = vtop - vbot
286
287    "CHOP" : BEGIN
288        chop = event.value
289        goto, set_gamma         ;And redraw
290        ENDCASE
291
292    "VALUES": BEGIN
293        use_values = event.value
294        ENDCASE
295
296    "HELP" : XDisplayFile, FILEPATH("xlct.txt", subdir=['help', 'widget']), $
297                TITLE = "Xlct Help", $
298                GROUP = event.top, $
299                WIDTH = 55, $
300                HEIGHT = 16
301
302    "RESTORE" : BEGIN                   ;Restore the original tables
303        r_curr = (r_orig = r0)
304        g_curr = (g_orig = g0)
305        b_curr = (b_orig = b0)
306        tvlct, r_curr, g_curr, b_curr
307        xlct_show
308        ENDCASE
309
310    "OVERWRITE" : BEGIN                 ;overwrite original tables
311        r0 = (r_orig = r_curr)
312        g0 = (g_orig = g_curr)
313        b0 = (b_orig = b_curr)
314    reset_all:
315        WIDGET_CONTROL, top, SET_VALUE = 100
316        WIDGET_CONTROL, bot, SET_VALUE = 0
317        WIDGET_CONTROL, g_slider, SET_VALUE = 50
318        vbot = 0
319        vtop = 100
320        gamma = 1.0
321        GOTO, set_gamma
322        ENDCASE
323
324    "REVERSE" : BEGIN                   ;Reverse the table
325        l = lindgen(ncolors) + cbot
326        r_orig[cbot] = reverse(r_orig[l])
327        g_orig[cbot] = reverse(g_orig[l])
328        b_orig[cbot] = reverse(b_orig[l])
329        goto, set_gamma                 ;And redraw
330        ENDCASE
331
332    "DONE": BEGIN
333        WIDGET_CONTROL, event.top, /DESTROY
334        r0 = 0 & g0 = 0 & b0 = 0  ;Free common
335        if PTR_VALID(p_updt_cb_data) then PTR_FREE, p_updt_cb_data
336        ENDCASE
337
338    "NEWBASE": BEGIN
339        mode = event.value
340        b = ([0, 0, 1])[mode]           ;Top base to map: 0 or 1.
341        for i=0,1 do WIDGET_CONTROL, state.bases[i], MAP=i eq b
342        if b eq 0 then begin            ;table or option mode?
343           b = ([2,3,0])[mode]          ;bottom base to map (mode eq 0 or 1)
344           for i=2,3 do WIDGET_CONTROL, state.bases[i], MAP=i eq b
345           endif
346        if mode eq 2 then begin
347            reset_all = 1
348            xlct_psave                  ;Save old state
349            plot, [0, ncolors-1], [0, ncolors-1], xstyle=3, $
350                ystyle=3, xmargin = [1,1], ymargin=[1,1], ticklen = -0.03, $
351                /NODATA, $
352                xtickname = replicate(' ', 10), ytickname = replicate(' ', 10)
353            goto, interp_cps
354            endif
355       
356        ENDCASE
357
358    "TFUNR": BEGIN
359     reset_tfun:
360        xlct_psave
361        xlct_draw_cps, -1, 0    ;Erase all
362        tfun = cps              ;Linear ramp
363        goto, interp_cps
364        ENDCASE
365
366    "REMCP": BEGIN
367        n = n_elements(cps)
368        if n gt 2 then begin
369          xlct_psave
370          xlct_draw_cps, -1, 0
371          igap = 0
372          for i=0, n-2 do $
373                if (cps[i+1] - cps[i]) lt (cps[igap+1]-cps[igap]) then $
374                        igap = i
375          keep = where(indgen(n) ne (igap > 1))
376          cps = cps[keep]
377          tfun = tfun[keep]
378          goto, interp_cps
379          ENDIF
380        ENDCASE
381    "ADDCP": BEGIN
382        xlct_psave
383        xlct_draw_cps, -1, 0
384        igap = 0                        ;Find largest gap
385        for i=0, n_elements(cps)-2 do $
386                if (cps[i+1] - cps[i]) gt (cps[igap+1]-cps[igap]) then $
387                        igap = i
388        cps = [ cps[0:igap], (cps[igap]+cps[igap+1])/2, cps[igap+1:*]]
389        tfun = [ tfun[0:igap], (tfun[igap]+tfun[igap+1])/2, tfun[igap+1:*]]
390      interp_cps:  xlct_draw_cps, -1  ;Redraw new
391        xlct_transfer, /update
392        xlct_psave              ;Restore old points
393        if n_elements(reset_all) then goto, reset_all
394        ENDCASE
395ENDCASE
396
397END
398
399
400;+
401;
402; @file_comments
403; Like <proidl>XLOADCT</proidl> but fastest to write and call by default
404; the palette palette.tbl which can be in any directory
405;
406; @categories
407; Widget, Color
408;
409; @keyword FILE {default='palette.tbl'}
410; If this keyword is set, the file by the given name is used
411; instead of the file colors1.tbl in the IDL directory.  This
412; allows multiple IDL users to have their own color table file.
413;
414; @keyword GROUP
415; The widget ID of the widget that calls Xlct. When  this ID is
416; specified, a death of the caller results in a death of Xlct
417
418; @keyword NCOLORS {default=!D.TABLE_SIZE = all available colors}
419; number of colors to use. Use color indexes from BOTTOM to the
420; smaller of !D.TABLE_SIZE-1 and NCOLORS-1.
421;
422; @keyword BOTTOM {default=0.}
423; first color index to use. Use color indexes from BOTTOM to
424; BOTTOM+NCOLORS-1.
425;
426; @keyword SILENT
427; Normally, no informational message is printed when a color map
428; is loaded. If this keyword is present and zero, this message is printed.
429;
430; @keyword USE_CURRENT
431; If set, use the current color tables, regardless of
432; the contents of the COMMON block COLORS.
433;
434; @keyword MODAL {default=not run in modal mode}
435; If set, then XLCT runs in "modal" mode, meaning that
436; all other widgets are blocked until the user quits XLCT.
437; A group leader must be specified (via the GROUP keyword)
438; for the MODAL keyword to have any effect.
439;
440; @keyword BLOCK
441; Set this keyword to have XMANAGER block when this
442; application is registered.  By default the Xmanager
443; keyword NO_BLOCK is set to 1 to provide access to the
444; command line if active command line processing is available.
445; Note that setting BLOCK for this application will cause
446; all widget applications to block, not only this
447; application.  For more information see the NO_BLOCK keyword
448; to XMANAGER.
449;
450; @keyword UPDATECALLBACK
451; Set this keyword to a string containing the name of
452; a user-supplied procedure that will be called when the color
453; table is updated by XLCT.  The procedure may optionally
454; accept a keyword called DATA, which will be automatically
455; set to the value specified by the optional UPDATECBDATA keyword.
456;
457; @keyword UPDATECBDATA
458; Set this keyword to a value of any type. It will be
459; passed via the DATA keyword to the user-supplied procedure
460; specified via the UPDATECALLBACK keyword, if any. If the
461; UPDATECBDATA keyword is not set the value accepted by the
462; DATA keyword to the procedure specified by UPDATECALLBACK
463; will be undefined.
464;
465; @history
466; 5/5/1999 copy of xloadct par Sebastien Masson (smasson\@lodyc.jussieu.fr)
467;
468; @version
469; $Id$
470;
471;-
472;
473PRO xlct, SILENT=silent_f, GROUP=group, FILE=file, $
474          USE_CURRENT=use_current, NCOLORS = nc, BOTTOM=bottom, $
475          MODAL=modal, BLOCK=block, UPDATECALLBACK=updt_cb_name, $
476          UPDATECBDATA=updt_cb_data
477;
478  compile_opt idl2, strictarrsubs
479;
480
481   COMMON colors, r_orig, g_orig, b_orig, r_curr, g_curr, b_curr
482   COMMON xlct_com, r0, g0, b0, tfun, state, filename, cps, psave, pnt, $
483    top, bot, silent, chop, lock, g_lbl, vbot, vtop, g_slider, $
484    gamma, color, use_values, ncolors, cbot, siz, w_height, show_win, $
485    updt_callback, p_updt_cb_data
486
487
488   IF(XRegistered("xlct") NE 0) THEN return
489
490   IF N_ELEMENTS(block) EQ 0 THEN block=0
491   IF N_ELEMENTS(updt_cb_name) EQ 0 THEN updt_callback="" $
492   ELSE updt_callback=updt_cb_name
493   IF N_ELEMENTS(updt_cb_data) GT 0 THEN p_updt_cb_data=PTR_NEW(updt_cb_data) $
494   ELSE p_updt_cb_data=PTR_NEW()
495
496   values_button = lonarr(2)
497
498   IF KEYWORD_SET(SILENT_f) THEN silent = SILENT_F ELSE silent = 1
499;-----------------------------------------------------------------------------
500; Changes made by S.Masson
501;-----------------------------------------------------------------------------
502   IF N_ELEMENTS(file) GT 0 THEN filename = file ELSE BEGIN
503      filename = (find('palette.tbl', /firstfound, /nopro))[0]
504      if filename EQ 'NOT FOUND' then filename=filepath('colors1.tbl',subdir=['resource', 'colors'])
505   ENDELSE
506   file = filename
507;-----------------------------------------------------------------------------
508   siz = 256                    ;Basic width of tool
509   names = 0
510   LOADCT, GET_NAMES = names, FILE = file ;Get table names
511   w_height = 50                ;Height of ramp
512   cur_win = !D.WINDOW
513   lock = 0
514   chop = 0
515   vbot = 0
516   vtop = 100
517   gamma = 1.0
518   use_values=0
519
520
521; Bases:
522;  0 = slider base  (stretch bottom, stretch top, gamma)
523;  1 = transfer function drawable + buttons
524;  2 = color table list
525;  3 = options base  (sliders. top, stretch)
526
527   state = { bases: lonarr(4), draw: 0L, name_list: 0L }
528
529; DJC - Added modal keyword.
530; Moved "group_leader" keyword from XMANAGER to WIDGET_BASE.
531; Ignore modal keyword if a group leader is not supplied.
532   if (N_ELEMENTS(group) GT 0L) then $
533    base = WIDGET_BASE(TITLE="Xlct", /COLUMN, GROUP_LEADER=group, $
534                       MODAL=KEYWORD_SET(modal)) $
535   else $
536    base = WIDGET_BASE(TITLE="Xlct", /COLUMN)
537
538
539; Setting the managed attribute indicates our intention to put this app
540; under the control of XMANAGER, and prevents our draw widgets from
541; becoming candidates for becoming the default window on WSET, -1. XMANAGER
542; sets this, but doing it here prevents our own WSETs at startup from
543; having that problem.
544   WIDGET_CONTROL, /MANAGED, base
545
546
547   show = WIDGET_DRAW(base, YSIZE=w_height, XSIZE=siz, /FRAME, RETAIN = 2)
548   junk = WIDGET_BASE(base, /ROW)
549   done = WIDGET_BUTTON(junk, VALUE=' Done ', UVALUE = "DONE")
550   junk1 = WIDGET_BUTTON(junk, VALUE=' Help ', UVALUE = "HELP")
551
552   junk = CW_BGROUP(base, /ROW, /EXCLUSIVE, /NO_REL, $
553                    ['Tables', 'Options', 'Function'], $
554                    UVALUE='NEWBASE', SET_VALUE=0)
555
556   junk = widget_base(base)
557   for i=0,1 do state.bases[i] = WIDGET_BASE(junk, /COLUMN)
558
559   sbase=WIDGET_BASE(state.bases[0], /COLUMN)
560   bot = WIDGET_SLIDER(sbase, TITLE = "Stretch Bottom", MINIMUM = 0, $
561                       MAXIMUM = 100, VALUE = 0, /DRAG, UVALUE = "BOTTOM", xsize=siz)
562   top = WIDGET_SLIDER(sbase, TITLE = "Stretch Top", MINIMUM = 0, $
563                       MAXIMUM = 100, VALUE = 100, /DRAG, UVALUE = "TOP", xsize=siz)
564   g_lbl = WIDGET_LABEL(sbase, VALUE = STRING(1.0))
565   g_slider = WIDGET_slider(sbase, TITLE = "Gamma Correction", $
566                            MINIMUM = 0, MAXIMUM = 100, VALUE = 50, UVALUE = "GAMMA", $
567                            /SUPPRESS_VALUE, /DRAG, xsize=siz)
568
569   junk = WIDGET_BASE(sbase)
570   for i=2,3 do state.bases[i] = WIDGET_BASE(junk, /COLUMN)
571   DEVICE, GET_SCREEN = junk
572   if junk[1] le 768 then junk = 8 else junk = 16
573   state.name_list = WIDGET_LIST(state.bases[2], VALUE = names, ysize = junk)
574
575
576;               Drawable for transfer function
577
578   junk = WIDGET_BASE(state.bases[1], /COLUMN, /FRAME)
579   junk1 = WIDGET_BUTTON(junk, VALUE = 'Reset Transfer Function', $
580                         UVALUE='TFUNR')
581   junk1 = WIDGET_BUTTON(junk, VALUE='Add Control Point', UVALUE='ADDCP')
582   junk1 = WIDGET_BUTTON(junk, VALUE='Remove Control Point', UVALUE='REMCP')
583
584   state.draw = WIDGET_DRAW(state.bases[1], xsize = siz, ysize = siz, $
585                            /BUTTON_EVENTS, /MOTION_EVENTS)
586
587
588   opt_id = state.bases[3]
589   junk = CW_BGROUP(opt_id, /ROW, LABEL_LEFT='Sliders:', /EXCLUSIVE, /NO_REL, $
590                    ['Independent', 'Gang'], UVALUE='GANG', SET_VALUE=lock)
591   junk = CW_BGROUP(opt_id, /ROW, LABEL_LEFT = 'Top:',  /EXCLUSIVE, /NO_REL, $
592                    ['Clip', 'Chop'], SET_VALUE=chop, UVALUE='CHOP')
593   junk = CW_BGROUP(opt_id, /ROW, LABEL_LEFT='Stretch:',  /EXCLUSIVE, /NO_REL, $
594                    ['Indices', 'Intensity'], UVALUE='VALUES', $
595                    SET_VALUE=use_values)
596   junk = WIDGET_BUTTON(opt_id, VALUE='Reverse Table', $
597                        UVALUE="REVERSE", /NO_REL)
598   junk = WIDGET_BUTTON(opt_id, VALUE='REPLACE Original Table', $
599                        UVALUE = "OVERWRITE", /NO_REL)
600   junk = WIDGET_BUTTON(opt_id, VALUE='RESTORE Original Table', $
601                        UVALUE="RESTORE", /NO_REL)
602
603   WIDGET_CONTROL, state.bases[1], MAP=0 ;Tfun is not visible
604   WIDGET_CONTROL, state.bases[3], MAP=0 ;options are not visible
605
606   WIDGET_CONTROL, base, /REALIZE
607   WIDGET_CONTROL, state.draw, GET_VALUE=tmp
608
609   if n_elements(bottom) gt 0 then cbot = bottom else cbot = 0
610   ncolors = !d.table_size - cbot
611   if n_elements(nc) gt 0 then ncolors = ncolors < nc
612   if ncolors le 0 then message,'Number of colors is 0 or negative'
613
614   psave = { xlct_psave, win: !d.window, x: !x.s, y: !y.s , xtype: !x.type, $
615             ytype: !y.type, clip: !p.clip }
616;Our initial state
617   wset, tmp                    ;Initial graph
618   xlct_psave                   ;Save original scaling & window
619   plot, [0, ncolors-1], [0, ncolors-1], xstyle=3, ystyle=3, $
620    xmargin = [1,1], ymargin=[1,1], ticklen = -0.03, /NODATA
621   xlct_psave                   ;Restore original scaling & window
622
623                                ;If no common, use current colors
624   IF KEYWORD_SET(use_current) or N_ELEMENTS(r_orig) LE 0 THEN BEGIN
625      TVLCT, r_orig, g_orig, b_orig, /GET
626      r_curr = r_orig
627      b_curr = b_orig
628      g_curr = g_orig
629   ENDIF
630
631   r0 = r_curr                  ;Save original colors
632   g0 = g_curr
633   b0 = b_curr
634   color = ncolors + cbot -1
635   cps = [0, ncolors-1]
636   tfun = cps
637   pnt = -1
638
639   WIDGET_CONTROL, show, GET_VALUE=show_win
640   WSET, show_win
641
642; DJC - fixed color bar display bug.
643
644;TVSCL, BYTSCL(INDGEN(siz) # REPLICATE(1, w_height), top = ncolors-1)
645   TV, BYTE((FLOAT(ncolors)*FINDGEN(siz)/FLOAT(siz-1)) # $
646            REPLICATE(1, w_height)) + BYTE(cbot)
647
648   WSET, cur_win
649
650; DJC - moved GROUP_LEADER keyword to WIDGET_BASE.
651   XManager, "xlct", base, NO_BLOCK=(NOT(FLOAT(block))), $
652    MODAL=KEYWORD_SET(modal)
653
654END
Note: See TracBrowser for help on using the repository browser.