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

Last change on this file since 23 was 23, checked in by mmc, 19 years ago

Fixed the output processing to recognize messages
tagged with the prefix =RAPPTURE-???=> as Rappture
directives. The following directives are now recognized:

=RAPPTURE-PROGRESS=>percent message
=RAPPTURE-ERROR=>message
=RAPPTURE-RUN=>runfile

Also, added the Rappture::exec command to make it easy
to exec a tool within a wrapper script and handle stdout
and stderr messages properly.

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