BreakpointAnalyzer.st
author Claus Gittinger <cg@exept.de>
Wed, 18 Dec 2019 19:06:30 +0100
changeset 4614 60fcb6d008cf
parent 4467 4698a67f4800
child 4723 524785227024
permissions -rw-r--r--
regenerated

"{ Package: 'stx:libcomp' }"

"{ NameSpace: Smalltalk }"

Parser variableSubclass:#BreakpointAnalyzer
	instanceVariableNames:'messageSendMap'
	classVariableNames:''
	poolDictionaries:''
	category:'System-Compiler-Debugging'
!


!BreakpointAnalyzer methodsFor:'accessing'!

messageSendMap
    ^ messageSendMap
! !

!BreakpointAnalyzer methodsFor:'code generation hooks'!

messageNodeRewriteHookFor:aMessageNode
    "invoked whenever a message send node has been generated;
     gives subclasses a chance to rewrite (instrument) it"

    (messageSendMap at:(aMessageNode line) ifAbsentPut:[Bag new])
        add:(aMessageNode selector).

    ^ aMessageNode

    "Created: / 15-04-2013 / 15:32:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 16-04-2013 / 23:07:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 20-02-2019 / 10:49:33 / Claus Gittinger"
! !

!BreakpointAnalyzer methodsFor:'initialization'!

initialize
    super initialize.
    messageSendMap := Dictionary new.

    "Created: / 15-04-2013 / 15:29:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!BreakpointAnalyzer methodsFor:'private'!

genMakeArrayWith:elementExpressions
    "return a node to generate an array at runtime.
     Will generate:
        literal shallowCopy                                     (if all elements are literals)
     or else:
        Array with:el1 ... with:elN                             (if N <= 8)
     or:
        (Array new at:1 put:el1; ... at:N put:elN; yourself)    (otherwise)

     SIGH: duplicate code here, because the other implementation is on the class side,
     and shared by JavaScriptParser and regular Parser.
    "

    |numEl arrRec sel expr|

    (elementExpressions conform:#isConstant) ifTrue:[
        arrRec := ConstantNode type:#Array value:(elementExpressions collect:#value as:Array) from:-1 to:-1. "/ position -1 means artifitial node
        ^ self messageNodeRewriteHookFor:(MessageNode receiver:arrRec selector:#shallowCopy).
    ].

    arrRec := VariableNode globalNamed:#Array.
    arrRec startPosition: -1 endPosition: -1. "/ -1 means artifitial node

    numEl := elementExpressions size.

    (numEl between:1 and:8) ifTrue:[
        sel := #(
                  #'with:'
                  #'with:with:'
                  #'with:with:with:'
                  #'with:with:with:with:'
                  #'with:with:with:with:with:'
                  #'with:with:with:with:with:with:'
                  #'with:with:with:with:with:with:with:'
                  #'with:with:with:with:with:with:with:with:'
                ) at:numEl.

        ^ self messageNodeRewriteHookFor:(MessageNode
                    receiver:arrRec
                    selector:sel
                    args:elementExpressions).
    ].

    "/ array creation expression ...
    expr := MessageNode
                receiver:arrRec
                selector:#new:
                arg:(ConstantNode type:#Integer value:numEl from: -1 to: -1). "/ -1 means artifitial node
    expr := self messageNodeRewriteHookFor:expr.

    numEl == 0 ifTrue:[
        ^ expr.
    ].
    "/ followed by a bunch of #at:put: messages...
    elementExpressions keysAndValuesDo:[:idx :e |
        expr := (idx == 1 ifTrue:[MessageNode] ifFalse:[CascadeNode])
                    receiver:expr
                    selector:#at:put:
                    arg1:(ConstantNode type:#Integer value:idx from: -1 to:-1)"/ -1 means artifitial node
                    arg2:e
                    fold:false.
        expr := self messageNodeRewriteHookFor:expr.
    ].
    "/ followed by a #yourself: message...
    expr := CascadeNode
                receiver:expr
                selector:#yourself.
    expr := self messageNodeRewriteHookFor:expr.
    ^ expr

    "Modified: / 24-04-2013 / 21:09:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!BreakpointAnalyzer class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !