📄 t-gen-support.st
字号:
Object variableSubclass: #LR0Item
instanceVariableNames: 'leftHandSide preDotSymbols postDotSymbols translationSymbol '
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Support'!
LR0Item comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I represent a context-free grammar production with a ''dot'' somewhere in the right hand side. I''m used in the construction of LR(0), SLR(1), and LALR(1) parsers.
leftHandSide -> <preDotSymbols> . <postDotSymbols> => <translationSymbol>
Instance Variables:
leftHandSide <Symbol>
preDotSymbols <OrderedCollection of: (String + Symbol)>
postDotSymbols <OrderedCollection of: (String + Symbol)>
translationSymbol <String + Symbol> - used for generating abstract syntax trees.'!
!LR0Item methodsFor: 'state accessing'!
leftHandSide
^leftHandSide!
leftHandSide: argument
leftHandSide := argument!
postDotSymbols
^postDotSymbols!
postDotSymbols: argument
postDotSymbols := argument!
preDotSymbols
^preDotSymbols!
preDotSymbols: argument
preDotSymbols := argument!
translationSymbol
^translationSymbol!
translationSymbol: argument
translationSymbol := argument! !
!LR0Item methodsFor: 'copying'!
postCopy
super postCopy.
self preDotSymbols: self preDotSymbols copy.
self postDotSymbols: self postDotSymbols copy.
^self! !
!LR0Item methodsFor: 'private'!
makeGrammarProductionWithLeftHandSide: lhs rightHandSide: rhs
^self translationSymbol isNil
ifTrue: [GrammarProduction leftHandSide: lhs rightHandSide: rhs]
ifFalse: [TransductionGrammarProduction
leftHandSide: lhs
rightHandSide: rhs
translationSymbol: self translationSymbol]! !
!LR0Item methodsFor: 'conversion'!
asGrammarProduction
| rhs |
rhs := OrderedCollection new.
rhs addAll: self preDotSymbols.
rhs addAll: self postDotSymbols.
^self makeGrammarProductionWithLeftHandSide: self leftHandSide rightHandSide: rhs! !
!LR0Item methodsFor: 'accessing'!
augmentedGrammarStartSymbol
^self class augmentedGrammarStartSymbol!
endOfInputSymbol
^self class endOfInputSymbol! !
!LR0Item methodsFor: 'printing'!
printOn: aStream
self leftHandSide printOn: aStream.
aStream nextPutAll: ' -> '.
self preDotSymbols do:
[:sym |
sym printOn: aStream.
aStream space].
aStream nextPutAll: '. '.
self postDotSymbols do:
[:sym |
sym printOn: aStream.
aStream space]! !
!LR0Item methodsFor: 'operations'!
nextSymbol
"Answer the symbol immediately to the right of the dot and nil if none."
^self postDotSymbols isEmpty
ifTrue: [nil]
ifFalse: [self postDotSymbols first]!
shift
"Conceptually move the dot past the next symbol."
self atEnd ifFalse: [self preDotSymbols addLast: self postDotSymbols removeFirst]! !
!LR0Item methodsFor: 'testing'!
atEnd
^self postDotSymbols isEmpty!
isFinalStateItem
"A final state item is of the form '@@ -> S <endOfInput> . '."
^self atEnd and: [self leftHandSide = self augmentedGrammarStartSymbol]!
isLR0Item
^true! !
!LR0Item methodsFor: 'comparing'!
= anItem
^anItem isLR0Item
ifTrue: [self leftHandSide = anItem leftHandSide and: [self preDotSymbols = anItem preDotSymbols and: [self postDotSymbols = anItem postDotSymbols]]]
ifFalse: [false]!
hash
"This is redefined because = is redefined."
^self leftHandSide hash bitXor: (self preDotSymbols hash bitXor: self postDotSymbols hash)! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
LR0Item class
instanceVariableNames: ''!
!LR0Item class methodsFor: 'constants'!
augmentedGrammarStartSymbol
^#@@!
endOfInputSymbol
^Character endOfInput! !
!LR0Item class methodsFor: 'instance creation'!
initialItemForGrammar: grammar
"After conceptually augment the grammar with the production
'@@ -> S <endOfInput>', answer the initial item for construction
of the LR CFSM."
^self
leftHandSide: self augmentedGrammarStartSymbol
preDotSymbols: OrderedCollection new
postDotSymbols: (OrderedCollection with: grammar startSymbol with: self endOfInputSymbol)!
leftHandSide: arg1 preDotSymbols: arg2 postDotSymbols: arg3
| newMe |
newMe := self new.
newMe leftHandSide: arg1.
newMe preDotSymbols: arg2.
newMe postDotSymbols: arg3.
^newMe!
leftHandSide: arg1 preDotSymbols: arg2 postDotSymbols: arg3 translationSymbol: arg4
| newMe |
newMe := self new.
newMe leftHandSide: arg1.
newMe preDotSymbols: arg2.
newMe postDotSymbols: arg3.
newMe translationSymbol: arg4.
^newMe! !
Object subclass: #ProductionPartition
instanceVariableNames: 'leftHandSide problemProductions otherProductions '
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Support'!
ProductionPartition comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I represent a partition of productions for a given nonterminal into two sets, potentially problematic productions and others. I am currently used for detecting left-recursive productions and productions with common prefixes.
Instance Variables:
leftHandSide <Symbol> - the left hand side nonterminal of my productions.
problemProductions <Set of: GrammarProduction> - when used for left-recursion
<Set of: (Set of: GrammarProduction)> - when used for left-factoring.
otherProductions <Set of: GrammarProduction>.'!
!ProductionPartition methodsFor: 'adding'!
addOtherProduction: prod
self otherProductions add: prod!
addProblemProduction: prod
self problemProductions add: prod! !
!ProductionPartition methodsFor: 'testing'!
anyProblems
^self problemProductions isEmpty not! !
!ProductionPartition methodsFor: 'initialization'!
initWithLeftHandSide: lhs
self leftHandSide: lhs.
self problemProductions: Set new.
self otherProductions: Set new! !
!ProductionPartition methodsFor: 'state accessing'!
leftHandSide
^leftHandSide!
leftHandSide: argument
leftHandSide := argument!
otherProductions
^otherProductions!
otherProductions: argument
otherProductions := argument!
problemProductions
^problemProductions!
problemProductions: argument
problemProductions := argument! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
ProductionPartition class
instanceVariableNames: ''!
!ProductionPartition class methodsFor: 'instance creation'!
partitionProdSetForLeftFactoring: prodSet
"ProdSet contains all productions for a given nonterminal. Partition these
productions into two sets: a set of sets of problem productions with common
prefixes and all the rest. Answer the partitioned productions."
| prodPrefix newPP |
prodSet isEmpty ifTrue: [self error: 'cannot partition an empty prodSet'].
prodPrefix := SetDictionary new.
prodSet do: [:prod | prodPrefix at: (prod rightHandSide isEmpty
ifTrue: [self epsilon]
ifFalse: [prod rightHandSide first])
add: prod].
newPP := self new initWithLeftHandSide: prodSet first leftHandSide.
prodPrefix do: [:set | set size > 1
ifTrue: [newPP addProblemProduction: set]
ifFalse: [newPP addOtherProduction: set first]].
^newPP!
partitionProdSetForLeftRecursion: prodSet
"ProdSet contains all productions for a given nonterminal. Partition these
productions into two sets: left-recursive problem productions and other
non-left-recursive productions. Answer the partitioned productions."
| newPP |
prodSet isEmpty ifTrue: [self error: 'cannot partition an empty prodSet'].
newPP := self new initWithLeftHandSide: prodSet first leftHandSide.
prodSet do: [:prod | (prod rightHandSide isEmpty or: [prod leftHandSide ~= prod rightHandSide first])
ifTrue: [newPP addOtherProduction: prod]
ifFalse: [newPP addProblemProduction: prod]].
^newPP! !
!ProductionPartition class methodsFor: 'constants'!
epsilon
"Answer an object used to represent the empty string (epsilon)."
^EpsilonNode epsilon! !
Object variableSubclass: #Grammar
instanceVariableNames: 'nonterminals terminals productions startSymbol nullableNonterminals firstSets followSets '
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Support'!
Grammar comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I represent a context-free grammar. My two main responsibilities are to compute my first and follow sets and to perform certain grammar manipulations sometimes needed to construct certain classes of parsers. The two grammar manipulations currently supported are removal of left-recursion and common prefixes (left-factoring).
Instance Variables:
nonterminals <Set of: Symbol> - nonterminals are represented by Symbols.
terminals <Set of: String> - terminals are represented by Strings.
productions <OrderedCollection of: GrammarProduction> - order is only important from a logical point of veiw (i.e. for printing).
startSymbol <Symbol> - a nonterminal.
nullableNonterminals <Set of: Symbol> - those nonterminals that can derive epsilon in zero or more steps.
firstSets <SetDictionary from: Symbol to: Strings> - for each nonterminal, the terminals that could begin a sentence derivable from that nonterminal.
followSets <SetDictionary from: Symbol to: Strings> - for each nonterminal, the terminals that could appear immediately to the right of that nonterminal in some sentential form in some valid derivation sequence.'!
!Grammar methodsFor: 'initialization'!
computeNullableNonterminals
"Compute the set of nonterminals that can derive epsilon in one or more steps."
| nullables prevNullables |
nullables := ((self productions select: [:prod | prod rightHandSide isEmpty])
collect: [:prod | prod leftHandSide]) asSet.
prevNullables := Set new.
[nullables size ~= prevNullables size]
whileTrue:
[prevNullables := nullables.
nullables := prevNullables union: ((self productions select: [:prod | prod rightHandSideComprisedOf: prevNullables])
collect: [:prod | prod leftHandSide]) asSet].
self nullableNonterminals: nullables!
init
self initSymbols.
self isReduced ifTrue: [self initFirstAndFollow]!
initFirstAndFollow
self computeNullableNonterminals.
self computeFirstSets.
self computeFollowSets!
initSymbols
| terms nonterms |
terms := Set new.
nonterms := Set new.
self productions do:
[:prod |
nonterms add: prod leftHandSide.
prod rightHandSide do: [:sym | sym isTerminal
ifTrue: [terms add: sym]
ifFalse: [nonterms add: sym]]].
self terminals: terms.
self nonterminals: nonterms! !
!Grammar methodsFor: 'state accessing'!
firstSets
^firstSets!
firstSets: argument
firstSets := argument!
followSets
^followSets!
followSets: argument
followSets := argument!
nonterminals
^nonterminals!
nonterminals: argument
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -