⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 t-gen-scanningparsing.st

📁 編譯器的語法產生器
💻 ST
📖 第 1 页 / 共 3 页
字号:
BidirectionalEdgeLabeledDigraphNode variableSubclass: #LRParserState
	instanceVariableNames: 'reduceMap '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'T-gen-Scanning/Parsing'!
LRParserState comment:
'=================================================
    Copyright (c) 1992 by Justin O. Graver.
    All rights reserved (with exceptions).
    For complete information evaluate "Object tgenCopyright."
=================================================

I represent a node in an LR parser characteristic finite state machine.

Instance Variables:

	edgeLabelMap		<Dictionary from: symbols to: successors> - overridden from EdgeLabeledDigraphNode for efficiency since only deterministic FSAs are constructed.
	reduceMap		<SetDictionary from: symbols to: productions>'!


!LRParserState methodsFor: 'initialization'!

init

	super init.
	self edgeLabelMap: Dictionary new.		"overrides use of SetDictionary in superclass"
	self reduceMap: SetDictionary new! !

!LRParserState methodsFor: 'state accessing'!

reduceMap

	^reduceMap!

reduceMap: argument 

	reduceMap := argument! !

!LRParserState methodsFor: 'exception handling'!

standardErrorString

	^'unexpected token encountered:  '! !

!LRParserState methodsFor: 'printing'!

printOn: aStream 

	super printOn: aStream.
	aStream cr.
	self reduceMap printOn: aStream! !

!LRParserState methodsFor: 'lalr analysis'!

appendHashTo: sym 
	"Answer a new nonterminal or terminal with my hash value appended."

	| newSym |
	newSym := sym , self symbolSuffixSeparatorString , self hash printString.
	^sym isNonterminal
		ifTrue: [newSym asNonterminal]
		ifFalse: [newSym]!

buildLalrGrammarWith: stateDict originalGrammar: aGrammar 
	"Answer my corresponding LALR(1) grammar. The new productions will not be in any 
	particular order so we must be sure to locate and explicitly specify the new start symbol."

	| productions startSymbol pattern startSyms |
	productions := OrderedCollection new.
	self
		collectLalrProductionsIn: productions
		andProdMapsIn: stateDict
		traversedStates: Set new.
	pattern := aGrammar startSymbol , self symbolSuffixSeparatorString , '*'.
	startSyms := Set new.
	productions do: [:prod | (pattern match: prod leftHandSide) ifTrue: [startSyms add: prod leftHandSide]].
	startSyms size = 1
		ifTrue: [startSymbol := startSyms first]
		ifFalse: [self error: 'multiple start symbols in LALR grammar'].
	^self buildGrammarWithProductions: productions startSymbol: startSymbol!

collectLalrProductionsIn: aCollection andProdMapsIn: stateDict traversedStates: aSet 

	| newProds |
	(aSet includes: self)
		ifFalse: 
			[aSet add: self.
			self isReduceState ifTrue: [self
					reductionsDo: 
						[:prod | 
						newProds := self makeLalrProductionFor: prod.
						(stateDict includesKey: self)
							ifTrue: 
								["only need to retain data for conflict states"
								newProds do: [:np | (stateDict at: self)
										at: prod add: np leftHandSide]].
						aCollection addAll: newProds]].
			self successorsExceptSelfDo: [:state | state
					collectLalrProductionsIn: aCollection
					andProdMapsIn: stateDict
					traversedStates: aSet]]!

lalr1AnalyzeConflicts: stateSet originalGrammar: aGrammar 

	| conflictStateMap newGrammar prodMap prod follows conflictStates |
	conflictStates := Set new.
	conflictStateMap := Dictionary new: stateSet size.
	stateSet do: [:state | conflictStateMap at: state put: SetDictionary new].
	newGrammar := self buildLalrGrammarWith: conflictStateMap originalGrammar: aGrammar.
	"rebuild reduce maps for inconsistent states"
	stateSet do: 
		[:state | 
		state reduceMap: SetDictionary new.
		prodMap := conflictStateMap at: state.
		prodMap
			associationsDo: 
				[:assoc | 
				prod := assoc key.
				follows := Set new.
				assoc value do: [:nonterm | (newGrammar followSetOf: nonterm)
						do: [:term | follows add: (term copyUpToLast: self symbolSuffixSeparatorChar)]].
				follows do: [:term | state reduceBy: prod on: term]].
		state hasReduceReduceConflict | state hasShiftReduceConflict ifTrue: [conflictStates add: state]].
	^conflictStates isEmpty!

makeLalrProductionFor: prod 

	| stateSet rhs newProds lhs currState |
	stateSet := Set with: self.
	prod rightHandSide reverseDo: [:sym | stateSet := stateSet inject: Set new into: [:set :state | set union: (state predecessorLabelMap at: sym)]].
	newProds := Set new.
	stateSet do: 
		[:state | 
		lhs := state appendHashTo: prod leftHandSide.
		currState := state.
		rhs := OrderedCollection new.
		prod rightHandSide do: 
			[:sym | 
			rhs add: (currState appendHashTo: sym).
			currState := currState transitionFor: sym].
		newProds add: (self makeProductionWithLeftHandSide: lhs rightHandSide: rhs)].
	^newProds! !

!LRParserState methodsFor: 'building'!

goto: aState on: transitionSymbol 

	self addSuccessor: aState withEdgeLabeled: transitionSymbol.
	aState addPredecessor: self withEdgeLabeled: transitionSymbol! !

!LRParserState methodsFor: 'state transitions'!

actionFor: aTerminal 

	| action |
	(action := self reductionFor: aTerminal) isNil ifTrue: [(action := self transitionFor: aTerminal) isNil ifTrue: [action := self acceptSymbol]].
	^action! !

!LRParserState methodsFor: 'modifying'!

addSuccessor: node withEdgeLabeled: label 
	"overridden for Dictionary edgeLabelMap"

	(self edgeLabelMap includesKey: label)
		ifTrue: [self error: 'check it out'].
	self edgeLabelMap at: label put: node! !

!LRParserState methodsFor: 'accessing'!

successors
	"overriden for Dictionary edgeLabelMap"

	^self edgeLabelMap values! !

!LRParserState methodsFor: 'private'!

acceptSymbol

	^self class acceptSymbol!

buildGrammarWithProductions: prods startSymbol: aSymbol 

	^self grammarClass buildGrammarWithProductions: prods startSymbol: aSymbol!

grammarClass

	^Grammar!

grammarProductionClass

	^GrammarProduction!

makeProductionWithLeftHandSide: lhs rightHandSide: rhs 

	^self grammarProductionClass leftHandSide: lhs rightHandSide: rhs!

symbolSuffixSeparatorChar

	^self class symbolSuffixSeparatorChar!

symbolSuffixSeparatorString

	^String with: self symbolSuffixSeparatorChar! !

!LRParserState methodsFor: 'accessing reductions'!

reduceBy: aProduction on: aTerminal 

	self reduceMap at: aTerminal add: aProduction!

reductionFor: aSymbol 

	^self reduceMap
		at: aSymbol
		ifAbsent: [nil]
		ifNotUnique: [self error: 'reduce/reduce conflict in parser']! !

!LRParserState methodsFor: 'testing'!

hasReduceReduceConflict
	"Answer true if there is a reduce/reduce conflict in this state, and false 
	otherwise."

	^self reduceMap isDeterministic not!

hasShiftReduceConflict
	"Answer true if there is a shift/reduce conflict in this state, and false 
	otherwise."

	| reduceSyms shiftSyms |
	reduceSyms := self reduceMap keys.
	shiftSyms := self edgeLabelMap keys.
	^reduceSyms size + shiftSyms size ~= (reduceSyms union: shiftSyms) size!

isReduceState

	^self reduceMap isEmpty not! !

!LRParserState methodsFor: 'enumerating'!

reductionsDo: aBlock 
	"Evaluate aBlock for each of my reduce productions."

	self reduceMap elementsDo: aBlock! !

!LRParserState methodsFor: 'converting'!

spaceOptimizeMap
	"Predecessors are only needed for LALR(1) analysis."

	super spaceOptimizeMap.
	self predecessorLabelMap: nil! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

LRParserState class
	instanceVariableNames: ''!


!LRParserState class methodsFor: 'constants'!

acceptSymbol

	^#accept!

symbolSuffixSeparatorChar

	^$.! !

!LRParserState class methodsFor: 'class initialization'!

initialize
	"LRParserState initialize"

	self noTransitionSignal: (Signal new nameClass: self message: #noTransitionSymbol)! !

Object variableSubclass: #TokenClassification
	instanceVariableNames: 'tokenType action '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'T-gen-Scanning/Parsing'!
TokenClassification comment:
'=================================================
    Copyright (c) 1992 by Justin O. Graver.
    All rights reserved (with exceptions).
    For complete information evaluate "Object tgenCopyright."
=================================================

I represent a class of tokens. 

Instance Variables:
	tokenType	<String> - name of this token class.
	action		<Symbol + UndefinedObject> - a message selector that will be sent to the scanner (via #perform:) when a token with this type is recognized.'!


!TokenClassification methodsFor: 'state accessing'!

action

	^action!

action: argument 

	action := argument!

tokenType

	^tokenType!

tokenType: argument 

	tokenType := argument! !

!TokenClassification methodsFor: 'testing'!

isTokenClassification

	^true! !

!TokenClassification methodsFor: 'printing'!

printOn: aStream

	aStream nextPutAll: self tokenType.
	aStream nextPutAll: ' : {'.
	aStream nextPutAll: (self action isNil ifTrue: ['nil'] ifFalse: [self action]).
	aStream nextPutAll: '} ;'! !

!TokenClassification methodsFor: 'reconstructing'!

reconstructOn: aStream 
	"Emit #( tokenType  action ) on aStream"

	aStream poundSign; leftParenthesis.
	self tokenType reconstructOn: aStream.
	aStream space.
	self action reconstructOn: aStream.
	aStream rightParenthesis! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

TokenClassification class
	instanceVariableNames: ''!


!TokenClassification class methodsFor: 'instance creation'!

tokenType: arg1 action: arg2 

	| newMe |
	newMe := self new.
	newMe tokenType: arg1.
	newMe action: arg2.
	^newMe! !

Object variableSubclass: #GrammarProduction
	instanceVariableNames: 'leftHandSide rightHandSide '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'T-gen-Scanning/Parsing'!
GrammarProduction comment:
'=================================================

⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -