compiler/PPCSequenceNode.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Tue, 12 May 2015 01:24:03 +0100
changeset 459 4751c407bb40
parent 452 9f4558b3be66
child 461 5986bf6d7d60
child 502 1e45d3c96ec5
permissions -rw-r--r--
Merged with PetitCompiler-JanKurs.20150510144201, PetitCompiler-Tests-JanKurs.20150510144201, PetitCompiler-Extras-Tests-JanKurs.20150510144201, PetitCompiler-Benchmarks-JanKurs.20150510144201 Name: PetitCompiler-JanKurs.20150510144201 Author: JanKurs Time: 10-05-2015, 04:42:29.192 PM UUID: 58a4786b-1182-4904-8b44-a13d3918f244 Name: PetitCompiler-Tests-JanKurs.20150510144201 Author: JanKurs Time: 10-05-2015, 04:32:12.870 PM UUID: 2a8fd41a-331b-4dcf-a7a3-752a50ce86e7 Name: PetitCompiler-Extras-Tests-JanKurs.20150510144201 Author: JanKurs Time: 10-05-2015, 04:59:25.308 PM UUID: ef43bd1a-be60-4e88-b749-8b635622c969 Name: PetitCompiler-Benchmarks-JanKurs.20150510144201 Author: JanKurs Time: 10-05-2015, 05:04:54.561 PM UUID: d8e764fd-016b-46e2-9fc1-17c38c18f0e5

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

"{ NameSpace: Smalltalk }"

PPCListNode subclass:#PPCSequenceNode
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'PetitCompiler-Nodes'
!

!PPCSequenceNode methodsFor:'accessing'!

prefix
    ^ #seq
! !

!PPCSequenceNode methodsFor:'analysis'!

acceptsEpsilon
    ^ self acceptsEpsilonOpenSet: IdentitySet new.
!

acceptsEpsilonOpenSet: set
    set add: self.
    ^ self children allSatisfy: [:e | e acceptsEpsilonOpenSet: set ]
!

firstSetSuchThat: block into: aCollection openSet: aSet
    (aSet includes: self) ifTrue: [ ^ aCollection ].
    aSet add: self.
    
    (block value: self) ifTrue: [ aCollection add: self. ^ aCollection ].
    
    self children do: [ :child | 
        child firstSetSuchThat: block into: aCollection openSet: aSet.
        child acceptsEpsilon ifFalse: [ ^ aCollection ]
    ].
    ^ aCollection
!

firstSets: aFirstDictionary into: aSet suchThat: aBlock
    | nullable |
    
    "TODO JK: aBlock is ignored by now"
    children do: [ :node |
        nullable := false.
        (aFirstDictionary at: node) do: [ :each |
            each isNullable
                ifTrue: [ nullable := true ]
                ifFalse: [ aSet add: each ] ].
        nullable
            ifFalse: [ ^ self ] ].
    aSet add: PPCSentinelNode instance
!

recognizedSentencesPrim
    | retval |
    (self children anySatisfy: [ :child | child hasFiniteLanguage not ]) ifTrue: [ ^ #() ].
    
    retval := Set with: ''.
    
    self children do: [ : child |
        | set |
        set := Set new.

        child recognizedSentences do: [ :suffix |
            retval do: [ :prefix |
                set add: prefix, suffix.
         		]
        ].
        retval := set.
    ].
    ^ retval asArray
! !

!PPCSequenceNode methodsFor:'compiling'!

addGuard: compiler id: id
    |  guard firsts |
    (compiler guards not or: [(guard := PPCGuard on: self) makesSense not]) ifTrue: [ ^ self].

    firsts := (self firstSetSuchThat: [ :e | (e isKindOf: PPCTrimmingTokenNode) or: [ e isTerminal ] ]).

    
    (firsts allSatisfy: [ :e | e isKindOf: PPCTrimmingTokenNode ]) ifTrue: [  
        "If we start with trimming, we should invoke the whitespace parser"
        firsts anyOne compileWhitespace: compiler.
        
        compiler add: 'context atEnd ifTrue: [ ^ self error ].'.
        guard id: id, '_guard'.
        guard compileGuard: compiler.
        compiler addOnLine: 'ifFalse: [ ^ self error ].'
    ].

    (firsts allSatisfy: [ :e | e isTerminal ]) ifTrue: [  
        compiler add: 'context atEnd ifTrue: [ ^ self error ].'.
        guard id: id, '_guard'.
        guard compileGuard: compiler.
        compiler addOnLine: 'ifFalse: [ ^ self error ].'
    ].
! !

!PPCSequenceNode methodsFor:'first follow next'!

followSets: aFollowDictionary firstSets: aFirstDictionary into: aSet suchThat: aBlock
    children keysAndValuesDo: [ :index :node |
        | follow first |
        follow := aFollowDictionary at: node.
        index = children size
            ifTrue: [ follow addAll: aSet ]
            ifFalse: [
                (self class withAll: (children 
                    copyFrom: index + 1 to: children size))
                        firstSets: aFirstDictionary
                        into: (first := IdentitySet new)
                        suchThat: aBlock.
                (first anySatisfy: [ :each | each isNullable ])
                    ifTrue: [ follow addAll: aSet ].
                follow addAll: (first 
                    reject: [ :each | each isNullable ]) ] ]
! !

!PPCSequenceNode methodsFor:'visiting'!

accept: visitor
    ^ visitor visitSequenceNode: self
! !