ContextInspectorView.st
author claus
Mon, 06 Feb 1995 02:01:18 +0100
changeset 57 36e13831b62d
parent 56 d0cb937cbcaa
child 73 e332d9c71624
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1993 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.
"

InspectorView subclass:#ContextInspectorView
	 instanceVariableNames:'inspectedContext showingTemporaries'
	 classVariableNames:''
	 poolDictionaries:''
	 category:'Interface-Inspector'
!

ContextInspectorView comment:'
COPYRIGHT (c) 1993 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libtool/ContextInspectorView.st,v 1.8 1995-02-06 00:59:36 claus Exp $
'!

!ContextInspectorView class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1993 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/ContextInspectorView.st,v 1.8 1995-02-06 00:59:36 claus Exp $
"
!

documentation
"
    a modified Inspector for Contexts (used in Debugger)
"
! !

!ContextInspectorView methodsFor:'initialization'!

initialize
    super initialize.
    showingTemporaries := false.
!

initializeListViewMiddleButtonMenus
    menu1 := PopUpMenu
		  labels:(resources array:#(
					    'inspect'
					    'basicInspect'
					    '-'
					    'show temporaries'
					   ))
	       selectors:#(
			   doInspect
			   doBasicInspect
			   nil
			   showTemporaries
			  )
		receiver:self
		     for:listView.
! !

!ContextInspectorView methodsFor:'accessing'!

inspect:con
    "set the context to be inspected"

    |aList homeContext method names rec sel implementorClass 
     argNames varNames tmpNames m|

    inspectedObject := nil.
    inspectedContext := con.
    self initializeListViewMiddleButtonMenus.
    listView setMiddleButtonMenu:menu1.

    con isNil ifTrue:[
	inspectedValues := nil.
	listView contents:nil.
	^ self
    ].

"/    realized ifFalse:[^ self].

    homeContext := con methodHome.

    homeContext isNil ifTrue:[
	"its a cheap blocks context"
	rec := con receiver.
	sel := con selector.
	names := #().
    ] ifFalse:[
	rec := homeContext receiver.
	sel := homeContext selector.

"/        implementorClass := homeContext searchClass whichClassImplements:sel.
	implementorClass := homeContext methodClass.
	implementorClass notNil ifTrue:[
	    method := implementorClass compiledMethodAt:sel.
	    method notNil ifTrue:[
		method isWrapped ifTrue:[
		    m := method originalMethod.
		    m notNil ifTrue:[
			method := m.
		    ]
		].
	    ].
	    method notNil ifTrue:[
		method source notNil ifTrue:[
		    names := method methodArgAndVarNames.
		    names isNil ifTrue:[
			names := #()
		    ]
		]
	    ]
	].
    ].

    "create dummy names (if there is no source available)"
    names isNil ifTrue:[
	names := OrderedCollection new.
	1 to:homeContext numArgs do:[:index |
	    names add:('mArg' , index printString)
	].
	1 to:homeContext nvars do:[:index |
	    names add:('mVar' , index printString)
	].
	showingTemporaries ifTrue:[
	    1 to:homeContext ntemp do:[:index |
		names add:('mTmp' , index printString)
	    ]
	]
    ].

    aList := OrderedCollection new.

    "
     stupid: should find the block via the contexts
     method-home and put real names in here
    "
    con isBlockContext ifTrue:[
	argNames := (1 to:(con numArgs)) collect:[:i | 'arg' , i printString].
	aList addAll:argNames.
	varNames := (1 to:(con nvars)) collect:[:i | 'var' , i printString].
	aList addAll:varNames.

	showingTemporaries ifTrue:[
	    tmpNames := (1 to:(con ntemp)) collect:[:i | 'tmp' , i printString].
	    aList addAll:tmpNames.
	].

	aList addAll:names.

	inspectedValues := Array withAll:(con argsAndVars).
	(showingTemporaries and:[con ntemp ~~ 0]) ifTrue:[
	    inspectedValues := inspectedValues , con temporaries
	].
	homeContext notNil ifTrue:[
	    inspectedValues := inspectedValues , homeContext argsAndVars.
	    (showingTemporaries and:[homeContext ntemp ~~ 0])ifTrue:[
		inspectedValues := inspectedValues , homeContext temporaries
	    ].
	].

    ] ifFalse:[
	aList addAll:names.
	inspectedValues := homeContext argsAndVars
    ].
    listView contents:aList.

    workspace contents:nil.
    self setDoitActionIn:workspace for:con.
!

release
    "release inspected object"

    inspectedContext := nil.
    super release
! !

!ContextInspectorView methodsFor:'private'!

setDoitActionIn:aWorkspace for:aContext
    aWorkspace doItAction:[:theCode |
	Compiler evaluate:theCode
		       in:aContext
		 receiver:nil
		notifying:aWorkspace
		   logged:true 
		   ifFail:nil
    ]
! !

!ContextInspectorView methodsFor:'user actions'!

doAccept:theText
    |value|

    selectedLine notNil ifTrue:[
	value := Compiler evaluate:theText
			  receiver:inspectedObject 
			 notifying:workspace.

	"yes, you can do that with a context"
	inspectedContext at:selectedLine put:value.
    ].
!

showTemporaries
    menu1 labelAt:#showTempraries put:(resources string:'hide temporaries').
    menu1 selectorAt:#showTempraries put:#hideTemporaries.
    showingTemporaries := true.
    self inspect:inspectedContext
!

hideTemporaries
    menu1 labelAt:#hideTempraries put:(resources string:'show temporaries').
    menu1 selectorAt:#hideTempraries put:#showTemporaries.
    showingTemporaries := false.
    self inspect:inspectedContext
! !