InspectorView.st
author claus
Thu, 09 Mar 1995 11:59:29 +0100
changeset 80 78f9581c78c6
parent 79 d78f92a07d5d
child 93 dda97353e775
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

'From Smalltalk/X, Version:2.10.4 on 28-feb-1995 at 2:12:00 am'!

View subclass:#InspectorView
	 instanceVariableNames:'listView workspace inspectedObject selectedLine nShown hasMore'
	 classVariableNames:'DefaultIcon'
	 poolDictionaries:''
	 category:'Interface-Inspector'
!

InspectorView comment:'
COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libtool/InspectorView.st,v 1.19 1995-03-09 10:59:29 claus Exp $
'!

!InspectorView class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

version
"
$Header: /cvs/stx/stx/libtool/InspectorView.st,v 1.19 1995-03-09 10:59:29 claus Exp $
"
!

documentation
"
    This class implements an graphical inspector.
    Inspecting can be done on an object -
    (where its instvarnames/values are inspected)
    or a list of objects (where a namearray/valuesarray is inspected).
    The later is used by the debugger to inspect method variables/args.

    The system calls the inspector through the global variable 'Inspector'
    which is bound to this class (but could be redefined - it actually is
    set to MiniInspector in a smalltalk without graphical user interface).

    Also notice, that there are two methods to inspect an object:
    sending #basicInspect to any object, will open this kind of inspector on 
    it (showing instance variables which are physically present).

    Sending it #inspect, will - depending on the object - sometimes invoke a
    specialized inspector. 
    (see OrderedCollectionInspectorView, ImageInspectorView etc. as examples).

    examples:
	    #(1 2 3 4) asOrderedCollection inspect
	    #(1 2 3 4) asOrderedCollection basicInspect
	    (Array new:10000) inspect
	    (Image fromFile:'bitmaps/claus.gif') inspect
	    (Image fromFile:'bitmaps/claus.gif') basicInspect
	    (Image fromFile:'bitmaps/SBrowser.xbm') inspect
	    (Image fromFile:'bitmaps/SBrowser.xbm') basicInspect
"
! !

!InspectorView class methodsFor:'instance creation'!

openOn:anObject
    "create and launch a new inspector for anObject"

    |topView inspectorView nm|

    anObject isClass ifTrue:[
	nm := anObject displayString
    ].
    nm isNil ifTrue:[
	nm := anObject classNameWithArticle
    ].

    topView := StandardSystemView
		    label:('Inspector on: ' , nm)
		     icon:self defaultIcon
		minExtent:(100 @ 100).

    topView extent:(Display extent // 3).

    inspectorView := self origin:(0.0 @ 0.0)
			  corner:(1.0 @ 1.0)
			     in:topView.

    "kludge: must realize first, to be able to set menu again"
    topView open.
    inspectorView inspect:anObject.
    ^ inspectorView

    "
     InspectorView openOn:(5 @ 7)
     InspectorView openOn:(Array new:400)
     DictionaryInspectorView openOn:(IdentityDictionary new)
    "
!

for:anObject
    "create and launch a new inspector for anObject.
     This protocol is a historic leftover - this method will vanish."

    ^ self openOn:anObject
!

inspect:anObject
    "create and launch a new inspector for anObject.
     This protocol is a historic leftover - this method will vanish."

    ^ self openOn:anObject
! !

!InspectorView class methodsFor:'defaults'!

defaultIcon
    DefaultIcon isNil ifTrue:[
	DefaultIcon := Form fromFile:'Inspector.xbm' resolution:100
    ].
    ^ DefaultIcon
! !

!InspectorView methodsFor:'accessing'!

inspect:anObject
    "define the object to be inspected"

    |aList sameObject|

    sameObject := anObject == inspectedObject.
    inspectedObject := anObject.

    hasMore := false.
    aList := self fieldList.
    hasMore ifTrue:[
	aList add:' ... '
    ].

    sameObject ifTrue:[
	listView setContents:aList.
"/        listView selection:1.
    ] ifFalse:[
	listView contents:aList
    ].

    workspace contents:nil.
    self setDoItAction.

    selectedLine := nil
!

listView
    ^ listView
! !

!InspectorView methodsFor:'private'!

setDoItAction
    workspace doItAction:[:theCode |
	(inspectedObject class compilerClass) 
	    evaluate:theCode 
	    in:nil 
	    receiver:inspectedObject 
	    notifying:workspace 
	    logged:true 
	    ifFail:nil 
    ].

!

showMore
    hasMore ifTrue:[
	nShown := nShown * 2.
	self inspect:inspectedObject
    ]
!

fieldList 
    "return a list of names to show in the selectionList.
     Leave hasMore as true, if a '...' entry should be added."

    |aList n cls s|

    aList := OrderedCollection new.
    aList add:'self'.
    cls := inspectedObject class.
    cls isClass ifTrue:[
	cls allInstVarNames do:[:instVarName |
	    aList add:instVarName
	]
    ] ifFalse:[
	1 to:cls instSize do:[:index |
	    aList add:('instvar' , index printString)
	]
    ].
    cls isVariable ifTrue:[
	n := inspectedObject basicSize.
	(n > nShown) ifTrue:[
	    n := nShown.
	    hasMore := true.
	].
	(inspectedObject respondsTo:#keys) ifTrue:[
	    s := ReadStream on:(inspectedObject keys).
	    1 to:n do:[:index |
		aList add:(s next printString)
	    ]
	] ifFalse:[
	    1 to:n do:[:index |
		aList add:(index printString)
	    ]
	].
    ].
    ^ aList
! !

!InspectorView methodsFor:'user interaction'!

showSelection:lineNr
    "user clicked on an instvar - show value in workspace"

    |val string index|

    (hasMore and:[lineNr == listView list size]) ifTrue:[
	"clicked on the '...' entry"
	self showMore.
	listView selection:lineNr.
    ].

    lineNr == 1 ifTrue:[
	"selecting self also does a re-set, this allows updating the list"
	self inspect:inspectedObject.
    ].
    val := self valueAtLine:lineNr.
    string := val displayString.
    workspace replace:string.
    selectedLine := lineNr.
!

destroy
    inspectedObject := nil.
    super destroy
!

valueAtLine:lineNr
    "helper - return the value of the selected entry"

    |index instSize|

    lineNr == 1 ifTrue:[
	^ inspectedObject
    ].
    index := lineNr - 1.   "/ skip self
    instSize := inspectedObject class instSize.

    (inspectedObject class isVariable not
    or:[index <= instSize]) ifTrue:[
	^ inspectedObject instVarAt:index
    ].
    index := index - instSize.
    ^ inspectedObject basicAt:index
!

doInspect
    "user selected inspect-menu entry"

    self doInspect:false
!

doInspect:basic
    "user selected inspect-menu entry"

    |objectToInspect|

    selectedLine notNil ifTrue:[
	objectToInspect := self valueAtLine:selectedLine.
	basic ifTrue:[
	    objectToInspect basicInspect
	] ifFalse:[
	    objectToInspect inspect
	]
    ]
!

doBasicInspect
    "user selected inspect-menu entry"

    self doInspect:true 
!

keyPress:aKey x:x y:y
    "all my input is passed on to the workspace-field"

    workspace keyPress:aKey x:0 y:0
!

update:something with:someArgument from:changedObject
    "handle updates from other inspectors"

    |oldSelection|

    changedObject == inspectedObject ifTrue:[
	oldSelection := listView selection.
	self inspect:inspectedObject.
	oldSelection notNil ifTrue:[
	    self showSelection:oldSelection
	]
    ]
!

doAccept:theText
    |value index|

    value := inspectedObject class compilerClass 
		 evaluate:theText
		 receiver:inspectedObject 
		 notifying:workspace.

    selectedLine notNil ifTrue:[
	selectedLine == 1 ifFalse:[
	    index := selectedLine - 1.
	    (inspectedObject class isVariable) ifFalse:[
		inspectedObject instVarAt:index put:value
	    ] ifTrue:[
		index <= (inspectedObject class instSize) ifTrue:[
		    inspectedObject instVarAt:index put:value
		] ifFalse:[
		    index := index - inspectedObject class instSize.
		    inspectedObject basicAt:index put:value
		]
	    ]
	]
    ].
    inspectedObject changed
!

inspectOwners
    "open an inspector on owners of the inspectedObject.
     (this is a secret function)"

    self withCursor:(Cursor questionMark) do:[
	|owners dict|

	owners := (ObjectMemory whoReferences:inspectedObject) asOrderedCollection.
	owners size > 500 ifTrue:[
	    (self confirm:'there are ' , owners size printString , ' owners.\\Do you really want to see them all ?' withCRs)
	    ifFalse:[^ self]
	].
	dict := IdentityDictionary new.
	owners do:[:owner |
	    |set names oClass|

	    owner ~~ self ifTrue:[
		set := Set new.
		names := owner class allInstVarNames.
		oClass := owner class.
		1 to:oClass instSize do:[:i |
		    (owner instVarAt:i) == inspectedObject ifTrue:[
			set add:(names at:i).
		    ].
		].
		oClass isVariable ifTrue:[
		    oClass isPointers ifTrue:[
			1 to:owner basicSize do:[:i |
			    (owner basicAt:i) == inspectedObject ifTrue:[
				 set add:i
			    ]
			]
		    ]
		].
		dict at:owner put:set
	    ].
	].
	dict inspect
    ]
! !

!InspectorView methodsFor:'initialization'!

mapped
    "delayed setup of lists till map-time - 
     this makes startup of inspectors a bit faster"

    |o|

    super mapped.
    "
     kludge to trick inspect:, which ignores setting the
     same object again ...
    "
    o := inspectedObject.
    inspectedObject := nil.
    self inspect:o
!

initialize
    |v panel|

    super initialize.

    panel := VariableHorizontalPanel 
		origin:(0.0 @ 0.0)
		corner:(1.0 @ 1.0)
		in:self.

    v := HVScrollableView 
		for:SelectionInListView 
		miniScrollerH:true
		miniScrollerV:false
		in:panel.
    v origin:(0.0 @ 0.0) corner:(0.3 @ 1.0).

    listView := v scrolledView.
    listView action:[:lineNr | self showSelection:lineNr].
    listView doubleClickAction:[:lineNr | self doInspect].
    listView ignoreReselect:false.
    listView model:self; menu:#fieldMenu.

    v := HVScrollableView 
		for:CodeView 
		miniScrollerH:true
		miniScrollerV:false
		in:panel.
    v origin:(0.3 @ 0.0) corner:(1.0 @ 1.0).
    workspace := v scrolledView.

    workspace acceptAction:[:theText | self doAccept:theText asString].

    nShown := 100.
    hasMore := false.
!

fieldMenu
    |labels selectors|

    hasMore ifTrue:[
	labels := #(
		      'inspect'
		      'basicInspect'
		      '-'
		      'show more'
		   ).

	selectors := #(
		      doInspect 
		      doBasicInspect 
		      nil 
		      showMore
		      ).
    ] ifFalse:[
	labels := #(
		      'inspect'
		      'basicInspect'
"/                      '-'
"/                      'owners'
		   ).

	selectors := #(
		      doInspect 
		      doBasicInspect 
"/                      nil
"/                      inspectOwners
		      ).
    ].

    ^ PopUpMenu
	  labels:(resources array:labels)
	  selectors:selectors
! !

!InspectorView methodsFor:'release'!

release
    "release inpected object. This is normally not needed,
     since the garbage collector will find this memory alone.
     However, if some applications keeps inspectors (for example,
     the debugger does this), this would be freed very late."

"
    inspectedObject notNil ifTrue:[
	inspectedObject removeDependent:self
    ].
"
    inspectedObject := nil.
    workspace doItAction:nil.
    workspace contents:nil.
    listView contents:nil
! !