source: trunk/SRC/ToBeReviewed/COULEURS/xlct.pro @ 114

Last change on this file since 114 was 114, checked in by smasson, 18 years ago

new compilation options (compile_opt idl2, strictarrsubs) in each routine

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