source: trunk/gui/scripts/deviceViewer1D.tcl @ 738

Last change on this file since 738 was 738, checked in by mmc, 17 years ago

Fixed a problem recently introduced with device structures on the
input side. app-rtd was having trouble changing the structure when
you changed devices via the loader.

Fix for support ticket #1631 'can't read "_axis(click-x)": no such
variable'. Added some code to guard against the case when release
gets called somehow before click.

Fix for support ticket #1688 'can't use empty string as operand of "-"'
Fix for support ticket #1689 'divide by zero'
Fix for support ticket #1707 'can't read "_dobj2cols(-energy)":
no such element in array'
All of these fixes had to do with the energy viewer, particularly
in the case where there was only 1 energy level, so the homo/lumo
levels could not be displayed.

Fix for support ticket #1704 'impossible limits (min 1.58489 >=
max 6.30957e-05)'
Added some code to guard against setting limits where min >= max.

File size: 29.4 KB
Line 
1# ----------------------------------------------------------------------
2#  COMPONENT: deviceViewer1D - visualizer for 1D device geometries
3#
4#  This widget is a simple visualizer for 1D devices.  It takes the
5#  Rappture XML representation for a 1D device and draws various
6#  facets of the data.  Each facet shows the physical layout along
7#  with some other quantity.  The "Electrical" facet shows electrical
8#  contacts.  The "Doping" facet shows the doping profile, and so
9#  forth.
10# ======================================================================
11#  AUTHOR:  Michael McLennan, Purdue University
12#  Copyright (c) 2004-2005  Purdue Research Foundation
13#
14#  See the file "license.terms" for information on usage and
15#  redistribution of this file, and for a DISCLAIMER OF ALL WARRANTIES.
16# ======================================================================
17package require Itk
18package require BLT
19
20option add *DeviceViewer1D.padding 4 widgetDefault
21option add *DeviceViewer1D.deviceSize 0.25i widgetDefault
22option add *DeviceViewer1D.deviceOutline black widgetDefault
23option add *DeviceViewer1D*graph.width 3i widgetDefault
24option add *DeviceViewer1D*graph.height 2i widgetDefault
25
26itcl::class Rappture::DeviceViewer1D {
27    inherit itk::Widget
28
29    itk_option define -device device Device ""
30
31    constructor {owner args} { # defined below }
32    destructor { # defined below }
33
34    public method add {dataobj {settings ""}}
35    public method get {}
36    public method delete {args}
37
38    public method controls {option args}
39    public method download {option args}
40                                                                               
41    protected method _loadDevice {}
42    protected method _loadParameters {frame path}
43    protected method _changeTabs {}
44    protected method _fixSize {}
45    protected method _fixAxes {}
46    protected method _align {}
47
48    protected method _marker {option {name ""} {path ""}}
49
50    protected method _controlCreate {container libObj path}
51    protected method _controlSet {widget libObj path}
52
53    private variable _owner ""      ;# thing managing this control
54    private variable _dlist ""      ;# list of dataobj objects
55    private variable _dobj2raise    ;# maps dataobj => raise flag
56    private variable _device ""     ;# XML library with <structure>
57    private variable _tab2fields    ;# maps tab name => list of fields
58    private variable _field2parm    ;# maps field path => parameter name
59    private variable _units ""      ;# units for field being edited
60    private variable _marker        ;# marker currently being edited
61}
62                                                                               
63itk::usual DeviceViewer1D {
64}
65
66# ----------------------------------------------------------------------
67# CONSTRUCTOR
68# ----------------------------------------------------------------------
69itcl::body Rappture::DeviceViewer1D::constructor {owner args} {
70    set _owner $owner
71
72    pack propagate $itk_component(hull) no
73
74    itk_component add tabs {
75        blt::tabset $itk_interior.tabs -borderwidth 0 -relief flat \
76            -side bottom -tearoff 0 \
77            -selectcommand [itcl::code $this _changeTabs]
78    } {
79        keep -activebackground -activeforeground
80        keep -background -cursor -font
81        rename -highlightbackground -background background Background
82        keep -highlightcolor -highlightthickness
83        keep -tabbackground -tabforeground
84        rename -selectbackground -background background Background
85        rename -selectforeground -foreground foreground Foreground
86    }
87    pack $itk_component(tabs) -expand yes -fill both
88
89    itk_component add -protected inner {
90        frame $itk_component(tabs).inner
91    }
92
93    itk_component add top {
94        frame $itk_component(inner).top
95    }
96    pack $itk_component(top) -fill x
97
98    itk_component add layout {
99        Rappture::DeviceLayout1D $itk_component(inner).layout
100    }
101    pack $itk_component(layout) -side top -fill x -pady 4
102
103    itk_component add graph {
104        blt::graph $itk_component(inner).graph \
105            -highlightthickness 0 -plotpadx 0 -plotpady 0
106    } {
107        keep -background -foreground -cursor -font
108    }
109    pack $itk_component(graph) -expand yes -fill both
110    $itk_component(graph) legend configure -hide yes
111
112    bind $itk_component(graph) <Configure> "
113        [list after cancel [list catch [itcl::code $this _align]]]
114        [list after 100 [list catch [itcl::code $this _align]]]
115    "
116
117    itk_component add geditor {
118        Rappture::Editor $itk_component(graph).editor \
119            -activatecommand [itcl::code $this _marker activate] \
120            -validatecommand [itcl::code $this _marker validate] \
121            -applycommand [itcl::code $this _marker apply]
122    }
123
124    itk_component add devcntls {
125        Rappture::Notebook $itk_component(inner).devcntls
126    }
127    pack $itk_component(devcntls) -side bottom -fill x
128
129    eval itk_initialize $args
130
131    _fixSize
132}
133
134# ----------------------------------------------------------------------
135# DESTRUCTOR
136# ----------------------------------------------------------------------
137itcl::body Rappture::DeviceViewer1D::destructor {} {
138    set _device ""
139    foreach name [array names _tab2fields] {
140        eval itcl::delete object $_tab2fields($name)
141    }
142    after cancel [list catch [itcl::code $this _fixAxes]]
143    after cancel [list catch [itcl::code $this _align]]
144    after cancel [list catch [itcl::code $this _loadDevice]]
145}
146
147# ----------------------------------------------------------------------
148# USAGE: add <dataobj> ?<settings>?
149#
150# Clients use this to add a data object to the plot.  The optional
151# <settings> are used to configure the plot.  Allowed settings are
152# -color, -brightness, -width, -linestyle, and -raise. Only
153# -brightness and -raise do anything.
154# ----------------------------------------------------------------------
155itcl::body Rappture::DeviceViewer1D::add {dataobj {settings ""}} {
156    array set params {
157        -color auto
158        -brightness 0
159        -width 1
160        -raise 0
161        -linestyle solid
162        -description ""
163    }
164    foreach {opt val} $settings {
165        if {![info exists params($opt)]} {
166            error "bad settings \"$opt\": should be [join [lsort [array names params]] {, }]"
167        }
168        set params($opt) $val
169    }
170 
171    set pos [lsearch -exact $dataobj $_dlist]
172
173    if {$pos < 0} {
174        if {![Rappture::library isvalid $dataobj]} {
175            error "bad value \"$dataobj\": should be Rappture::library object"
176        }
177
178        lappend _dlist $dataobj
179        set _dobj2raise($dataobj) $params(-raise)
180
181        after cancel [list catch [itcl::code $this _loadDevice]]
182        after idle [list catch [itcl::code $this _loadDevice]]
183    }
184}
185
186# ----------------------------------------------------------------------
187# USAGE: get
188#
189# Clients use this to query the list of objects being plotted, in
190# order from bottom to top of this result.
191# ----------------------------------------------------------------------
192itcl::body Rappture::DeviceViewer1D::get {} {
193    # put the dataobj list in order according to -raise options
194    set dlist $_dlist
195    foreach obj $dlist {
196        if {[info exists _dobj2raise($obj)] && $_dobj2raise($obj)} {
197            set i [lsearch -exact $dlist $obj]
198            if {$i >= 0} {
199                set dlist [lreplace $dlist $i $i]
200                lappend dlist $obj
201            }
202        }
203    }
204    return $dlist
205}
206
207# ----------------------------------------------------------------------
208# USAGE: delete ?<dataobj> <dataobj> ...?
209#
210# Clients use this to delete a dataobj from the plot. If no dataobjs
211# are specified, then all dataobjs are deleted.
212# ----------------------------------------------------------------------
213itcl::body Rappture::DeviceViewer1D::delete {args} {
214    if {[llength $args] == 0} {
215        set args $_dlist
216    }
217
218    # delete all specified dataobjs
219    set changed 0
220    foreach dataobj $args {
221        set pos [lsearch -exact $_dlist $dataobj]
222        if {$pos >= 0} {
223            set _dlist [lreplace $_dlist $pos $pos]
224            catch {unset _dobj2raise($dataobj)}
225            set changed 1
226        }
227    }
228
229    # if anything changed, then rebuild the plot
230    if {$changed} {
231        after cancel [list catch [itcl::code $this _loadDevice]]
232        after idle [list catch [itcl::code $this _loadDevice]]
233    }
234}
235
236# ----------------------------------------------------------------------
237# USAGE: controls insert <pos> <xmlobj> <path>
238#
239# Clients use this to add a control to the internal panels of this
240# widget.  Such controls are usually placed at the top of the widget,
241# but if possible, they are integrated directly onto the device
242# layout or the field area.
243# ----------------------------------------------------------------------
244itcl::body Rappture::DeviceViewer1D::controls {option args} {
245    switch -- $option {
246        insert {
247            if {[llength $args] != 3} {
248                error "wrong # args: should be \"controls insert pos xmlobj path\""
249            }
250            set pos [lindex $args 0]
251            set xmlobj [lindex $args 1]
252            set path [lindex $args 2]
253            if {[string match *structure.parameters* $path]} {
254            } elseif {[string match structure.components* $path]} {
255                $itk_component(layout) controls insert $pos $xmlobj $path
256            }
257        }
258        default {
259            error "bad option \"$option\": should be insert"
260        }
261    }
262}
263
264
265# ----------------------------------------------------------------------
266# USAGE: download coming
267# USAGE: download controls <downloadCommand>
268# USAGE: download now
269#
270# Clients use this method to create a downloadable representation
271# of the plot.  Returns a list of the form {ext string}, where
272# "ext" is the file extension (indicating the type of data) and
273# "string" is the data itself.
274# ----------------------------------------------------------------------
275itcl::body Rappture::DeviceViewer1D::download {option args} {
276    switch $option {
277        coming {
278            # nothing to do
279        }
280        controls {
281            # no controls for this download yet
282            return ""
283        }
284        now {
285            return ""  ;# not implemented yet!
286        }
287        default {
288            error "bad option \"$option\": should be coming, controls, now"
289        }
290    }
291}
292
293# ----------------------------------------------------------------------
294# USAGE: _loadDevice
295#
296# Used internally to search for fields and create corresponding
297# tabs whenever a device is installed into this viewer.
298# ----------------------------------------------------------------------
299itcl::body Rappture::DeviceViewer1D::_loadDevice {} {
300    set _device [lindex [get] end]
301
302    #
303    # Release any info left over from the last device.
304    #
305    foreach name [array names _tab2fields] {
306        eval itcl::delete object $_tab2fields($name)
307    }
308    catch {unset _tab2fields}
309    catch {unset _field2parm}
310
311    if {[winfo exists $itk_component(top).cntls]} {
312        $itk_component(top).cntls delete 0 end
313    }
314
315    #
316    # Scan through the current device and extract the list of
317    # fields.  Create a tab for each field.
318    #
319    if {$_device != ""} {
320        foreach nn [$_device children fields] {
321            set name [$_device get fields.$nn.about.label]
322            if {$name == ""} {
323                set name $nn
324            }
325
326            set fobj [Rappture::Field ::#auto $_device fields.$nn]
327            lappend _tab2fields($name) $fobj
328        }
329    }
330    set tabs [lsort [array names _tab2fields]]
331
332    if {[$itk_component(tabs) size] > 0} {
333        $itk_component(tabs) delete 0 end
334    }
335
336    if {[llength $tabs] <= 0} {
337        #
338        # No fields?  Then we don't need to bother with tabs.
339        # Just pack the inner frame directly.  If there are no
340        # fields, get rid of the graph.
341        #
342        pack $itk_component(inner) -expand yes -fill both
343        if {[llength $tabs] > 0} {
344            pack $itk_component(graph) -expand yes -fill both
345        } else {
346            pack forget $itk_component(graph)
347            $itk_component(layout) configure -leftmargin 0 -rightmargin 0
348        }
349    } else {
350        #
351        # Two or more fields?  Then create a tab for each field
352        # and select the first one by default.  Make sure the
353        # graph is packed.
354        #
355        pack forget $itk_component(inner)
356        pack $itk_component(graph) -expand yes -fill both
357
358        foreach name $tabs {
359            $itk_component(tabs) insert end $name \
360                -activebackground $itk_option(-background)
361        }
362        $itk_component(tabs) select 0
363    }
364
365    #
366    # Scan through and look for any parameters in the <structure>.
367    # Register any parameters associated with fields, so we can
368    # add them as active controls whenever we install new fields.
369    # Create controls for any remaining parameters, so the user
370    # can see that there's something to adjust.
371    #
372    if {$_device != ""} {
373        _loadParameters $itk_component(top) parameters
374    }
375
376    #
377    # Install the first tab
378    #
379    _changeTabs
380
381    #
382    # Fix the right margin of the graph so that it has enough room
383    # to display the right-hand edge of the device.
384    #
385    $itk_component(graph) configure \
386        -rightmargin [$itk_component(layout) extents bar3D]
387
388    _fixSize
389}
390
391# ----------------------------------------------------------------------
392# USAGE: _loadParameters <frame> <path>
393#
394# Used internally in _loadDevice to load child parameters at the
395# specified <path> into the <frame>.  If any of the children are
396# groups, then this is called recursively to fill in the group
397# children.
398# ----------------------------------------------------------------------
399itcl::body Rappture::DeviceViewer1D::_loadParameters {frame path} {
400    foreach cname [$_device children $path] {
401        set handled 0
402        set type [$_device element -as type $path.$cname]
403        if {$type == "about"} {
404            continue
405        }
406        if {$type == "number"} {
407            set name [$_device element -as id $path.$cname]
408
409            # look for a field that uses this parameter
410            set found ""
411            foreach fname [$_device children fields] {
412                foreach comp [$_device children fields.$fname] {
413                    set v [$_device get fields.$fname.$comp.constant]
414                    if {[string equal $v $name]} {
415                        set found "fields.$fname.$comp"
416                        break
417                    }
418                }
419                if {"" != $found} break
420            }
421
422            if {"" != $found} {
423                set _field2parm($found) $name
424                set handled 1
425            }
426        }
427
428        #
429        # Any parameter that was not handled above should be handled
430        # here, by adding it to a control panel above the device
431        # layout area.
432        #
433        if {!$handled} {
434            if {![winfo exists $frame.cntls]} {
435                Rappture::Controls $frame.cntls $_owner
436                pack $frame.cntls -expand yes -fill both
437            }
438            $frame.cntls insert end $path.$cname
439
440            #
441            # If this is a group, then we must add its children
442            # recursively.
443            #
444            if {$type == "group"} {
445                set gr [$frame.cntls control -value end]
446                _loadParameters [$gr component inner] $path.$cname
447            }
448        }
449    }
450}
451
452# ----------------------------------------------------------------------
453# USAGE: _changeTabs
454#
455# Used internally to change the field being displayed whenever a new
456# tab is selected.
457# ----------------------------------------------------------------------
458itcl::body Rappture::DeviceViewer1D::_changeTabs {} {
459    set graph $itk_component(graph)
460
461    #
462    # Figure out which tab is selected and make the inner frame
463    # visible in that tab.
464    #
465    set i [$itk_component(tabs) index select]
466    if {$i != ""} {
467        set name [$itk_component(tabs) get $i]
468        $itk_component(tabs) tab configure $name \
469            -window $itk_component(inner) -fill both
470    } else {
471        set name [lindex [array names _tab2fields] 0]
472    }
473
474    #
475    # Update the graph to show the current field.
476    #
477    eval $graph element delete [$graph element names]
478    eval $graph marker delete [$graph marker names]
479
480    foreach {zmin zmax} [$itk_component(layout) limits] { break }
481    if {$zmin != "" && $zmin < $zmax} {
482        $graph axis configure x -min $zmin -max $zmax
483    }
484
485    if {$_device != ""} {
486        set units [$_device get units]
487        if {$units != "arbitrary"} {
488            $graph axis configure x -hide no -title "Position ($units)"
489        } else {
490            $graph axis configure x -hide yes
491        }
492    } else {
493        $graph axis configure x -hide no -title "Position"
494    }
495
496    # turn on auto limits
497    $graph axis configure y -min "" -max ""
498
499    set flist ""
500    if {[info exists _tab2fields($name)]} {
501        set flist $_tab2fields($name)
502    }
503
504    set n 0
505    foreach fobj $flist {
506        catch {unset hints}
507        array set hints [$fobj hints]
508
509        if {[info exists hints(units)]} {
510            set _units $hints(units)
511            $graph axis configure y -title "$name ($hints(units))"
512        } else {
513            set _units ""
514            $graph axis configure y -title $name
515        }
516
517        if {[info exists hints(scale)]
518              && [string match log* $hints(scale)]} {
519            $graph axis configure y -logscale yes
520        } else {
521            $graph axis configure y -logscale no
522        }
523
524        foreach comp [$fobj components] {
525            # can only handle 1D meshes here
526            if {[$fobj components -dimensions $comp] != "1D"} {
527                continue
528            }
529
530            set elem "elem[incr n]"
531            set xv [$fobj mesh $comp]
532            set yv [$fobj values $comp]
533
534            $graph element create $elem -x $xv -y $yv \
535                -color black -symbol "" -linewidth 2
536
537            if {[info exists hints(color)]} {
538                $graph element configure $elem -color $hints(color)
539            }
540
541            foreach {path x y val} [$fobj controls get $comp] {
542                if {$path != ""} {
543                    set id "control[incr n]"
544                    $graph marker create text -coords [list $x $y] \
545                        -text $val -anchor s -name $id -background ""
546                    $graph marker bind $id <Enter> \
547                        [itcl::code $this _marker enter $id]
548                    $graph marker bind $id <Leave> \
549                        [itcl::code $this _marker leave $id]
550                    $graph marker bind $id <ButtonPress> \
551                        [itcl::code $this _marker edit $id $fobj/$path]
552                }
553            }
554        }
555    }
556
557    # let the widget settle, then fix the axes to "nice" values
558    after cancel [list catch [itcl::code $this _fixAxes]]
559    after 100 [list catch [itcl::code $this _fixAxes]]
560}
561
562# ----------------------------------------------------------------------
563# USAGE: _fixSize
564#
565# Used internally to fix the overall size of this widget based on
566# the various parts inside.  Sets the requested width/height of the
567# widget so that it is big enough to display the device and its
568# fields.
569# ----------------------------------------------------------------------
570itcl::body Rappture::DeviceViewer1D::_fixSize {} {
571    update idletasks
572    set w [winfo reqwidth $itk_component(tabs)]
573    set h [winfo reqheight $itk_component(tabs)]
574    component hull configure -width $w -height $h
575}
576
577# ----------------------------------------------------------------------
578# USAGE: _fixAxes
579#
580# Used internally to adjust the y-axis limits of the graph to "nice"
581# values, so that any control marker associated with the value,
582# for example, remains on screen.
583# ----------------------------------------------------------------------
584itcl::body Rappture::DeviceViewer1D::_fixAxes {} {
585    set graph $itk_component(graph)
586    if {![winfo ismapped $graph]} {
587        after cancel [list catch [itcl::code $this _fixAxes]]
588        after 100 [list catch [itcl::code $this _fixAxes]]
589        return
590    }
591
592    #
593    # HACK ALERT!
594    # Use this code to fix up the y-axis limits for the BLT graph.
595    # The auto-limits don't always work well.  We want them to be
596    # set to a "nice" number slightly above or below the min/max
597    # limits.
598    #
599    set log [$graph axis cget y -logscale]
600    $graph axis configure y -min "" -max ""
601    foreach {min max} [$graph axis limits y] { break }
602
603    if {$log} {
604        set min [expr {0.9*$min}]
605        set max [expr {1.1*$max}]
606    } else {
607        if {$min > 0} {
608            set min [expr {0.95*$min}]
609        } else {
610            set min [expr {1.05*$min}]
611        }
612        if {$max > 0} {
613            set max [expr {1.05*$max}]
614        } else {
615            set max [expr {0.95*$max}]
616        }
617    }
618
619    # bump up the max so that it's big enough to show control markers
620    set fnt $itk_option(-font)
621    set h [expr {[font metrics $fnt -linespace] + 5}]
622    foreach mname [$graph marker names] {
623        set xy [$graph marker cget $mname -coord]
624        foreach {x y} [eval $graph transform $xy] { break }
625        set y [expr {$y-$h}]  ;# find top of text in pixels
626        foreach {x y} [eval $graph invtransform [list 0 $y]] { break }
627        if {$y > $max} { set max $y }
628    }
629
630    if {$log} {
631        set min [expr {pow(10.0,floor(log10($min)))}]
632        set max [expr {pow(10.0,ceil(log10($max)))}]
633    } else {
634        set min [expr {0.1*floor(10*$min)}]
635        set max [expr {0.1*ceil(10*$max)}]
636    }
637
638    $graph axis configure y -min $min -max $max
639
640    after cancel [list catch [itcl::code $this _align]]
641    after 100 [list catch [itcl::code $this _align]]
642}
643
644# ----------------------------------------------------------------------
645# USAGE: _align
646#
647# Used internally to align the margins of the device layout and the
648# graph, so that two areas line up.
649# ----------------------------------------------------------------------
650itcl::body Rappture::DeviceViewer1D::_align {} {
651    set graph $itk_component(graph)
652
653    #
654    # Set the left/right margins of the layout so that it aligns
655    # with the graph.  Set the right margin of the graph so it
656    # it is big enough to show the 3D edge of the device that
657    # hangs over on the right-hand side.
658    #
659    update
660    foreach {xmin xmax} [$graph axis limits x] { break }
661    set lm [$graph xaxis transform $xmin]
662    $itk_component(layout) configure -leftmargin $lm
663
664    set w [winfo width $graph]
665    set rm [expr {$w-[$graph xaxis transform $xmax]}]
666    $itk_component(layout) configure -rightmargin $rm
667}
668
669# ----------------------------------------------------------------------
670# USAGE: _marker enter <name>
671# USAGE: _marker leave <name>
672# USAGE: _marker edit <name> <path>
673# USAGE: _marker activate
674# USAGE: _marker validate <value>
675# USAGE: _marker apply <value>
676#
677# Used internally to manipulate the control markers draw on the
678# graph for a field.
679# ----------------------------------------------------------------------
680itcl::body Rappture::DeviceViewer1D::_marker {option {name ""} {path ""}} {
681    switch -- $option {
682        enter {
683            $itk_component(graph) marker configure $name -background #e5e5e5
684            #
685            # BE CAREFUL:  Need an update here to force the graph to
686            #   refresh itself or else a subsequent click on the
687            #   marker will ignore the text that was recently changed,
688            #   and fail to generate a <ButtonPress> event!
689            #
690            update idletasks
691        }
692        leave {
693            $itk_component(graph) marker configure $name -background ""
694            #
695            # BE CAREFUL:  Need an update here to force the graph to
696            #   refresh itself or else a subsequent click on the
697            #   marker will ignore the text that was recently changed,
698            #   and fail to generate a <ButtonPress> event!
699            #
700            update idletasks
701        }
702        edit {
703            set _marker(name) $name
704            set _marker(fobj) [lindex [split $path /] 0]
705            set _marker(path) [lindex [split $path /] 1]
706            $itk_component(geditor) activate
707        }
708        activate {
709            set g $itk_component(graph)
710            set val [$g marker cget $_marker(name) -text]
711            foreach {x y} [$g marker cget $_marker(name) -coords] { break }
712            foreach {x y} [$g transform $x $y] { break }
713            set x [expr {$x + [winfo rootx $g] - 4}]
714            set y [expr {$y + [winfo rooty $g] - 5}]
715
716            set fnt $itk_option(-font)
717            set h [expr {[font metrics $fnt -linespace] + 2}]
718            set w [expr {[font measure $fnt $val] + 5}]
719
720            return [list text $val \
721                x [expr {$x-$w/2}] \
722                y [expr {$y-$h}] \
723                w $w \
724                h $h]
725        }
726        validate {
727            if {$_units != ""} {
728                if {[catch {Rappture::Units::convert $name \
729                        -context $_units -to $_units} result] != 0} {
730                    if {[regexp {^bad.*: +(.)(.+)} $result match first tail]
731                          || [regexp {(.)(.+)} $result match first tail]} {
732                        set result "[string toupper $first]$tail"
733                    }
734                    bell
735                    Rappture::Tooltip::cue $itk_component(geditor) $result
736                    return 0
737                }
738            }
739            if {[catch {$_marker(fobj) controls validate $_marker(path) $name} result]} {
740                bell
741                Rappture::Tooltip::cue $itk_component(geditor) $result
742                return 0
743            }
744            return 1
745        }
746        apply {
747            if {$_units != ""} {
748                catch {Rappture::Units::convert $name \
749                    -context $_units -to $_units} value
750            } else {
751                set value $name
752            }
753
754            $_marker(fobj) controls put $_marker(path) $value
755            $_owner changed $_marker(path)
756            event generate $itk_component(hull) <<Edit>>
757
758            _changeTabs
759        }
760    }
761}
762
763# ----------------------------------------------------------------------
764# USAGE: _controlCreate <container> <libObj> <path>
765#
766# Used internally to create a gauge widget and pack it into the
767# given <container>.  When the gauge is set, it updates the value
768# for the <path> in the <libObj>.
769# ----------------------------------------------------------------------
770itcl::body Rappture::DeviceViewer1D::_controlCreate {container libObj path} {
771    set presets ""
772    foreach pre [$libObj children -type preset $path] {
773        lappend presets \
774            [$libObj get $path.$pre.value] \
775            [$libObj get $path.$pre.label]
776    }
777
778    set type Rappture::Gauge
779    set units [$libObj get $path.units]
780    if {$units != ""} {
781        set desc [Rappture::Units::description $units]
782        if {[string match temperature* $desc]} {
783            set type Rappture::TemperatureGauge
784        }
785    }
786
787    set counter 0
788    set w "$container.gauge[incr counter]"
789    while {[winfo exists $w]} {
790        set w "$container.gauge[incr counter]"
791    }
792
793    # create the widget
794    $type $w -units $units -presets $presets
795    pack $w -side top -anchor w
796    bind $w <<Value>> [itcl::code $this _controlSet $w $libObj $path]
797
798    set min [$libObj get $path.min]
799    if {"" != $min} { $w configure -minvalue $min }
800
801    set max [$libObj get $path.max]
802    if {"" != $max} { $w configure -maxvalue $max }
803
804    set str [$libObj get $path.default]
805    if {$str != ""} { $w value $str }
806
807    if {$type == "Rappture::Gauge" && "" != $min && "" != $max} {
808        set color [$libObj get $path.color]
809        if {$color == ""} {
810            set color blue
811        }
812        if {$units != ""} {
813            set min [Rappture::Units::convert $min -to $units -units off]
814            set max [Rappture::Units::convert $max -to $units -units off]
815        }
816        $w configure -spectrum [Rappture::Spectrum ::#auto [list \
817            $min white $max $color] -units $units]
818    }
819
820    set str [$libObj get $path.label]
821    if {$str != ""} {
822        set help [$libObj get $path.help]
823        if {"" != $help} {
824            append str "\n$help"
825        }
826        if {$units != ""} {
827            set desc [Rappture::Units::description $units]
828            append str "\n(units of $desc)"
829        }
830        Rappture::Tooltip::for $w $str
831    }
832
833    set str [$libObj get $path.icon]
834    if {$str != ""} {
835        $w configure -image [image create photo -data $str]
836    }
837}
838
839# ----------------------------------------------------------------------
840# USAGE: _controlSet <widget> <libObj> <path>
841#
842# Invoked automatically whenever an internal control changes value.
843# Queries the new value for the control and assigns the value to the
844# given <path> on the XML object <libObj>.
845# ----------------------------------------------------------------------
846itcl::body Rappture::DeviceViewer1D::_controlSet {widget libObj path} {
847    set newval [$widget value]
848    $libObj put $path.current $newval
849    event generate $itk_component(hull) <<Edit>>
850}
851
852# ----------------------------------------------------------------------
853# CONFIGURATION OPTION: -device
854#
855# Set to the Rappture::Library object representing the device being
856# displayed in the viewer.  If set to "", the viewer is cleared to
857# display nothing.
858# ----------------------------------------------------------------------
859itcl::configbody Rappture::DeviceViewer1D::device {
860    if {$itk_option(-device) != ""} {
861        if {![Rappture::library isvalid $itk_option(-device)]} {
862            error "bad value \"$itk_option(-device)\": should be Rappture::Library"
863        }
864    }
865
866    delete
867    if {"" != $itk_option(-device)} {
868        add $itk_option(-device)
869    }
870    _loadDevice
871}
Note: See TracBrowser for help on using the repository browser.