SmallSenseAbstractInstvarInterfaceExtractor.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Thu, 25 Jul 2013 11:34:26 +0100
changeset 39 748389119d0a
parent 32 658f47bc231e
permissions -rw-r--r--
Initial support for per-language edit support. Some work on Smalltalk edit support, namely on electric blocks. Works fine, but need more work to make it usable but not too intrusive.

"{ Package: 'jv:smallsense' }"

SmallSenseParser subclass:#SmallSenseAbstractInstvarInterfaceExtractor
	instanceVariableNames:'stack copied initialStack saveStacks input collector
		blockTraversal blockArgs'
	classVariableNames:''
	poolDictionaries:''
	category:'SmallSense-Roel Typer'
!


!SmallSenseAbstractInstvarInterfaceExtractor methodsFor:'extracting'!

extractInterfacesFrom:m addTo:aTypeCollector 
    |parser|

    method := m.
    saveStacks := Dictionary new.
    stack := OrderedCollection new.
     "0 to: method numTemps - 1 do: [:i | stack add: #temp -> i ]."
    initialStack := stack copy.
    collector := aTypeCollector.
    parser := SmalltalkXInstvarInterfaceExtractor new.
    parser setColector:aTypeCollector.
    input := parser 
                parseMethod:method source
                in:method mclass
                ignoreErrors:false
                ignoreWarnings:false.
    blockTraversal := false.
    blockArgs := 0.

    [ input isNil ] whileFalse:[
        self unaryExpressionFor:input.
        input :=input nextStatement.
    ]

    "Modified: / 24-11-2010 / 22:24:16 / Jakub <zelenja7@fel.cvut.cz>"
!

extractInterfacesFrom:sourc class:class addTo:aTypeCollector 
    |parser|

    saveStacks := Dictionary new.
    stack := OrderedCollection new.
     "0 to: method numTemps - 1 do: [:i | stack add: #temp -> i ]."
    initialStack := stack copy.
    collector := aTypeCollector.
    parser := SmalltalkXInstvarInterfaceExtractor new.
    parser setColector:aTypeCollector.
    input := parser 
                parseMethod: sourc
                in:class
                ignoreErrors:false
                ignoreWarnings:false.
    blockTraversal := false.
    blockArgs := 0.

    [ input isNil ] whileFalse:[
        self unaryExpressionFor:input.
        input :=input nextStatement.
    ]

    "Created: / 17-03-2011 / 16:00:31 / Jakub <zelenja7@fel.cvut.cz>"
! !

!SmallSenseAbstractInstvarInterfaceExtractor methodsFor:'opcodes-control'!

nativeSend: selector numArgs: na 
        | receiver args |
        args := stack removeLast: na.
        receiver := stack removeLast.
        receiver isInteger 
                ifTrue: 
                        [ collector 
                                addSend: selector
                                to: receiver ]
                ifFalse: 
                        [ receiver isVariableBinding ifTrue: 
                                [ receiver key = #temp 
                                        ifTrue: 
                                                [ collector 
                                                        addSend: selector
                                                        toTmp: receiver value ]
                                        ifFalse: 
                                                [ receiver key = #return ifTrue: 
                                                        [ collector 
                                                                addSend: selector
                                                                onReturnOfSelfMethod: receiver value ] ] ] ].
        (receiver = #self and: [ collector theClass methodDictionary includesKey: selector ]) ifTrue: 
                [ args doWithIndex: 
                        [ :arg :index | 
                        collector 
                                handleAssignment: arg
                                forTmp: index - 1
                                in: collector theClass >> selector ] ].
        stack add: (collector 
                        pushSendOf: selector
                        to: receiver
                        args: args)

    "Modified: / 18-05-2011 / 23:47:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

send: selector numArgs: na 
	^self 
		nativeSend: selector
		numArgs: na
! !

!SmallSenseAbstractInstvarInterfaceExtractor methodsFor:'opcodes-data movement'!

dupFirst
	stack add: stack last
!

pop
	stack removeLast
!

pushConstant: value
	value class == BlockClosure
		ifTrue:
			[self
				readBlock: value method
				copied: 0]
		ifFalse: [
			blockArgs := value.
			stack addLast: value class]
!

pushContext
	stack add: #context
!

pushInst: index
	stack add: index
!

pushReceiver
	stack addLast: #self
!

pushStatic: assoc
	"assoc can be an association OR a variable binding. I just push the complete association, since it does not interest me for the moment."

	stack addLast: assoc
! !

!SmallSenseAbstractInstvarInterfaceExtractor methodsFor:'private'!

copied: list
	copied := list
!

initialize
        super initialize.
        blockTraversal := false.
        blockArgs := 0.

    "Modified: / 03-11-2010 / 21:27:34 / Jakub <zelenja7@fel.cvut.cz>"
!

input
	^input
!

method: aMethod
	method := aMethod.
	copied := #()
!

readBlock: block copied: count
        | newCopied |
        newCopied := stack removeLast: count.
        stack add: #block.
        ^(self class new)
                copied: newCopied;
                extractInterfacesFrom: block source class:block mclass
                        addTo: collector

    "Modified: / 17-03-2011 / 16:01:39 / Jakub <zelenja7@fel.cvut.cz>"
!

reloadStack
        stack isNil
                ifTrue:
                        [stack := self saveStacks
                                at: self input startPosition
                                ifAbsent: [initialStack copy].
                        ^self].
        stack := self saveStacks
                at: self input startPosition
                ifAbsent: [stack]

    "Modified: / 28-10-2010 / 15:04:05 / Jakub <zelenja7@fel.cvut.cz>"
!

saveStacks
	saveStacks ifNil: [saveStacks := Dictionary new].
	^saveStacks
!

setColector:colectorSetter 
    collector := colectorSetter.

    "Created: / 03-11-2010 / 21:33:42 / Jakub <zelenja7@fel.cvut.cz>"
! !

!SmallSenseAbstractInstvarInterfaceExtractor class methodsFor:'documentation'!

version_HG

    ^ '$Changeset: <not expanded> $'
!

version_SVN
    ^ '$Id: SmallSenseAbstractInstvarInterfaceExtractor.st 7823 2011-11-26 16:55:59Z vranyj1 $'
! !