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

Last change on this file since 133 was 133, checked in by navarro, 18 years ago

english and nicer header (1)

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