ContextInspectorView.st
author Claus Gittinger <cg@exept.de>
Thu, 21 Nov 1996 16:36:35 +0100
changeset 868 b5f5f5723793
parent 840 ffc3caf94d23
child 947 b9625d9b0881
permissions -rw-r--r--
renamed vars for WIN32

"
 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 names showingTemporaries argsOnly'
	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 the Debugger)
    TODO:
        when expressions are evaluated in myself, the inst-var
        names are not known by the expression evaluator.
        This has to be fixed 
        (actual work is to be done in the Parser to allow passing of a context ...)

    [author:]
        Claus Gittinger

    [see also:]
        Context DebugView
"
! !

!ContextInspectorView methodsFor:'accessing'!

inspect:aContext
    "set the context to be inspected"

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

    (aContext == inspectedContext) ifTrue:[
        listView selection notNil ifTrue:[
            self showSelection:(listView selection).
        ].
        ^ self
    ].

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

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

"/    realized ifFalse:[^ self].

    homeContext := aContext methodHome.

    homeContext isNil ifTrue:[
        "its a cheap blocks context"
        rec := aContext receiver.
        sel := aContext 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.

                        "/ did it already allocate its locals ?
                        homeNames size - method methodArgNames size == homeContext numVars
                        ifFalse:[
                            homeNames := method methodArgNames.
                            argsOnly := true
                        ]
                    ]
                ]
            ].
        ].

        "
         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 numVars do:[:index |
                    homeNames add:('mVar' , index printString)
                ].
                showingTemporaries ifTrue:[
                    1 to:homeContext numTemps do:[:index |
                        homeNames add:('mTmp' , index printString)
                    ]
                ]
            ]
        ].
    ].

    "
     stupid: should find the block via the contexts
     method-home and put real names in here
    "
    aContext isBlockContext ifTrue:[
        method notNil ifTrue:[
            (aContext numArgs > 0
             or:[aContext numVars > 0]) ifTrue:[
                blockNode := Compiler 
                                blockAtLine:(aContext lineNumber)
                                in:method
                                numArgs:aContext numArgs
                                numVars:aContext numVars.
                blockNode notNil ifTrue:[
                    aContext numArgs > 0 ifTrue:[
                        vars := blockNode arguments.
                        vars size > 0 ifTrue:[
                            argNames := vars collect:[:var | var name]
                        ]
                    ].
                    aContext numVars > 0 ifTrue:[
                        vars := blockNode variables.
                        vars size > 0 ifTrue:[
                            varNames := vars collect:[:var | var name].
                        ]
                    ]
                ]
            ]
        ].

        names := OrderedCollection new.

        argNames isNil ifTrue:[
            argNames := (1 to:(aContext numArgs)) collect:[:i | 'arg' , i printString].
        ].

        names addAll:argNames.
        varNames isNil ifTrue:[
            varNames := (1 to:(aContext numVars)) collect:[:i | 'var' , i printString].
        ] ifFalse:[
            varNames size ~~ aContext numVars ifTrue:[
                varNames := varNames asOrderedCollection.
                varNames size+1 to:aContext numVars do:[:i |
                    varNames add:('var' , i printString)
                ]
            ]
        ].

        names addAll:varNames.

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

        names addAll:homeNames.
    ] ifFalse:[
        names := homeNames.
    ].

    listView list:names. 

    workspace contents:nil.
    self setDoitActionIn:workspace for:aContext.

    "Modified: 7.11.1996 / 17:21:21 / cg"
!

release
    "release inspected object"

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

    "Modified: 14.12.1995 / 21:49:43 / cg"
! !

!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'!

defaultLabel
    ^ 'locals'

    "
     ContextInspectorView openOn:thisContext sender
    "

    "Modified: 28.6.1996 / 16:07:49 / cg"
!

fieldList
    ^ names
!

hasSelfEntry
    ^ false

    "Created: 14.12.1995 / 19:29:47 / cg"
!

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"

    |homeContext theContext values|

    inspectedContext isNil ifTrue:[^ nil].

    argsOnly := false.
    theContext := inspectedContext.
    homeContext := theContext methodHome.

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

    ^ values at:lineNr.

    "Modified: 23.10.1996 / 16:21:05 / cg"
! !

!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
    "do not show contexts temporaries"

    showingTemporaries := false.
    self inspect:inspectedContext

    "Modified: 14.12.1995 / 19:24:44 / cg"
!

showTemporaries
    "show contexts temporaries"

    showingTemporaries := true.
    self inspect:inspectedContext

    "Modified: 14.12.1995 / 19:24:49 / cg"
! !

!ContextInspectorView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libtool/ContextInspectorView.st,v 1.29 1996-11-21 15:36:35 cg Exp $'
! !