compiler/PPCSequenceNode.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Thu, 30 Apr 2015 23:43:14 +0200
changeset 438 20598d7ce9fa
parent 422 116d2b2af905
child 452 9f4558b3be66
permissions -rw-r--r--
Updated to PetitCompiler-JanKurs.100, PetitCompiler-Tests-JanKurs.44 and PetitCompiler-Benchmarks-JanKurs.4 Name: PetitCompiler-JanKurs.100 Author: JanKurs Time: 30-04-2015, 10:48:52.165 AM UUID: 80196870-5921-46d9-ac20-a43bf5c2f3c2 Name: PetitCompiler-Tests-JanKurs.44 Author: JanKurs Time: 30-04-2015, 10:49:22.489 AM UUID: 348c02e8-18ce-48f6-885d-fcff4516a298 Name: PetitCompiler-Benchmarks-JanKurs.4 Author: JanKurs Time: 30-04-2015, 10:58:44.890 AM UUID: 18cadb42-f9ef-45fb-82e9-8469ade56c8b

"{ 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
! !

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