compiler/PPCTokenizingVisitor.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Tue, 12 May 2015 01:33:33 +0100
changeset 460 87a3d30ab570
parent 454 a9cd5ea7cc36
parent 459 4751c407bb40
child 461 5986bf6d7d60
permissions -rw-r--r--
Merge

"{ Package: 'stx:goodies/petitparser/compiler' }"

"{ NameSpace: Smalltalk }"

PPCRewritingVisitor subclass:#PPCTokenizingVisitor
	instanceVariableNames:'tokens'
	classVariableNames:''
	poolDictionaries:''
	category:'PetitCompiler-Visitors'
!

!PPCTokenizingVisitor methodsFor:'hooks'!

afterAccept: node retval: parserNode
    self isRoot ifTrue: [ 
        | tokenizerNode whitespaceNode |
        self change.
        tokens addLast: self eofToken.
        tokens do: [ :token | token unmarkForInline  ].
        
        whitespaceNode := tokens detect: [ :e | e isTrimmingTokenNode ] ifFound: [:token | 
                token whitespace copy
                    unmarkForInline;
                    name: 'consumeWhitespace';
                    yourself 
            ] ifNone: [
         		PPCNilNode new
                    name: 'consumeWhitespace';
                    yourself
            ].
        
        tokenizerNode := PPCTokenChoiceNode new
            children: tokens asArray;
            name: 'nextToken';
            yourself.
    
        ^ PPCTokenizingParserNode new
            parser: parserNode;
            tokenizer: tokenizerNode;
            whitespace: whitespaceNode;
            name: #'mainParser';
            yourself
    ].
    ^ parserNode

    "Modified: / 10-05-2015 / 07:27:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

eofToken
    | ws  |
    ws := PPCStarNode new
        child: (PPCMessagePredicateNode new
            message: #isSeparator;
            yourself);
        yourself.
    
    ^ PPCTrimmingTokenNode new
        child: PPCEndOfFileNode new;
        whitespace: ws;
        tokenClass: PPToken;
        yourself.
! !

!PPCTokenizingVisitor methodsFor:'initialization'!

initialize
    super initialize.
    tokens := OrderedCollection new.
! !

!PPCTokenizingVisitor methodsFor:'testing'!

isRoot
    ^ openSet size = 1
! !

!PPCTokenizingVisitor methodsFor:'tokens'!

addToken: token
    (tokens contains: [:e | e == token] ) ifFalse: [ 
        tokens addLast: token
    ]
! !

!PPCTokenizingVisitor methodsFor:'visiting'!

visitActionNode: node
    (node hasProperty: #trimmingToken) ifTrue: [ 
        self change.
        self addToken: node.
        
        ^ PPCTokenConsumeNode new
            child: node;
            yourself	
    ].

    ^ super visitActionNode: node
!

visitTokenNode: node
    self change.
    self addToken: node.
    
    ^ PPCTokenConsumeNode new
        child: node;
        yourself.
!

visitTrimmingTokenNode: node
    self change.
    self addToken: node.
    
    ^ PPCTokenConsumeNode new
        child: node;
        yourself.
! !