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