source: trunk/COULEURS/xlct.pro @ 2

Last change on this file since 2 was 2, checked in by opalod, 22 years ago

Initial revision

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