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

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

modification of some headers (+some corrections) to prepare usage of the new idldoc

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