ContextInspectorView.st
author Claus Gittinger <cg@exept.de>
Thu, 23 Nov 1995 18:44:21 +0100
changeset 200 01ce3d3636d5
parent 188 247042d21994
child 296 b480a51cfb5f
permissions -rw-r--r--
checkin from browser

"
 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 values names showingTemporaries'
	 classVariableNames:''
	 poolDictionaries:''
	 category:'Interface-Inspector'
!

!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.
"
!

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

!ContextInspectorView methodsFor:'accessing'!

inspect:con
    "set the context to be inspected"

    |homeContext method homeNames rec sel implementorClass 
     argNames varNames tmpNames m argsOnly|

    hasMore := false.
    inspectedObject := nil.
    inspectedContext := con.
    argsOnly := false.

    con isNil ifTrue:[
	names := nil.
	values := nil.
	listView list:nil. 
	^ self
    ].

"/    realized ifFalse:[^ self].

    homeContext := con methodHome.

    homeContext isNil ifTrue:[
	"its a cheap blocks context"
	rec := con receiver.
	sel := con selector.
	homeNames := OrderedCollection new.
    ] ifFalse:[
	rec := homeContext receiver.
	sel := homeContext selector.

	implementorClass := homeContext methodClass.
	implementorClass notNil ifTrue:[
	    method := implementorClass compiledMethodAt:sel.
	    method notNil ifTrue:[
		method isWrapped ifTrue:[
		    "
		     in a wrapped context, locals are something different
		    "
"/                    argsOnly := true.
		    m := method originalMethod.
		    m notNil ifTrue:[
			method := m.
		    ] ifFalse:[
			argsOnly := true.
		    ].
		].
	    ].
	    method notNil ifTrue:[
		method source notNil ifTrue:[
		    argsOnly ifTrue:[
			homeNames := method methodArgNames
		    ] ifFalse:[
			homeNames := method methodArgAndVarNames.
		    ]
		]
	    ].
	].

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

    "
     stupid: should find the block via the contexts
     method-home and put real names in here
    "
    con isBlockContext ifTrue:[
	names := OrderedCollection new.

	argNames := (1 to:(con numArgs)) collect:[:i | 'arg' , i printString].
	names addAll:argNames.
	varNames := (1 to:(con nvars)) collect:[:i | 'var' , i printString].
	names addAll:varNames.

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

	names addAll:homeNames.

	values := Array withAll:(con argsAndVars).
	(showingTemporaries and:[con ntemp ~~ 0]) ifTrue:[
	    values := values , con temporaries
	].
	homeContext notNil ifTrue:[
	    values := values , homeContext args.
	    argsOnly ifFalse:[
		values := values , homeContext vars.
		(showingTemporaries and:[homeContext ntemp ~~ 0])ifTrue:[
		    values := values , homeContext temporaries
		]
	    ].
	].

    ] ifFalse:[
	names := homeNames.
	argsOnly ifTrue:[
	    values := homeContext args
	] ifFalse:[
	    values := homeContext argsAndVars
	]
    ].

    listView list:names. 

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

release
    "release inspected object"

    inspectedContext := nil.
    names := values := nil.
    super release
! !

!ContextInspectorView methodsFor:'initialization'!

fieldMenu
    |labels selectors|

    showingTemporaries ifFalse:[
	labels := #(
		     'inspect'
		     'basicInspect'
		     '-'
		     'show temporaries'
		   ).
	selectors := #(
		     doInspect
		     doBasicInspect
		     nil
		     showTemporaries
		   )
    ] ifTrue:[
	labels := #(
		     'inspect'
		     'basicInspect'
		     '-'
		     'hide temporaries'
		   ).
	selectors := #(
		     doInspect
		     doBasicInspect
		     nil
		     hideTemporaries
		   )
    ].

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

initialize
    super initialize.
    showingTemporaries := false.

! !

!ContextInspectorView methodsFor:'private'!

fieldList
    ^ names
!

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

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

    ^ values at:lineNr.


! !

!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.
    ].
!

hideTemporaries
    showingTemporaries := false.
    self inspect:inspectedContext
!

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

    self showValue:(values at:lineNr).
    selectedLine := lineNr
!

showTemporaries
    showingTemporaries := true.
    self inspect:inspectedContext
! !

!ContextInspectorView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libtool/ContextInspectorView.st,v 1.18 1995-11-23 17:44:21 cg Exp $'
! !