📄 t-gen-scanningparsing.st
字号:
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I represent one production of a context-free grammar. I am responsible for some parts of the first/follow set computation algorithm and for converting myself between various related representations (e.g. LR(0) items).
Instance Variables:
leftHandSide <Symbol>
rightHandSide <OrderedCollection of: (String + Symbol)>'!
!GrammarProduction methodsFor: 'state accessing'!
leftHandSide
^leftHandSide!
leftHandSide: argument
leftHandSide := argument!
rightHandSide
^rightHandSide!
rightHandSide: argument
rightHandSide := argument! !
!GrammarProduction methodsFor: 'copying'!
postCopy
super postCopy.
self rightHandSide: self rightHandSide copy.
^self! !
!GrammarProduction methodsFor: 'parse tree building'!
computeResultNodeFor: builder withArgNodes: nodes
"Productions without translation symbols can only pass on a single argument
node."
nodes size = 1 ifFalse: [self error: 'Productions without translation symbols can only
pass on results from a single right-hand side nonterminal'].
^builder answerArgument: nodes first!
computeResultNodeFor: builder withTokenClassValue: value
"See this method in class TransductionGrammarProduction."
self error: 'No translation has been specified that would
create a place to store the token class value.'!
numberOfRhsNonterminals
"Answer the number of nonterminals in my right-hand side."
^(self rightHandSide select: [:sym | sym isNonterminal]) size! !
!GrammarProduction methodsFor: 'testing'!
hasSingleTokenClassRhs
"Answer true if my right hand side consists solely of
a single token class terminal symbol and false otherwise."
^self rightHandSide size = 1 and: [self rightHandSide first isTokenClassTerminal]!
hasTranslation
"See class TransductionGrammarProduction."
^false!
isEpsilonProduction
"Answer true if I am a production of the form S -> <epsilon> (i.e. if my right hand
side is empty) and false otherwise."
^self rightHandSide isEmpty!
isGrammarProduction
^true!
rightHandSideComprisedOf: aSet
"Answer true if all symbols in my right-hand side
are included in aSet and false otherwise."
self rightHandSide detect: [:sym | (aSet includes: sym) not]
ifNone: [^true].
^false!
rightHandSideHasAllNontermsIn: aSet
"Answer true if all nonterminals in my right-hand side
are included in aSet and false otherwise."
self rightHandSide detect: [:sym | sym isNonterminal and: [(aSet includes: sym) not]]
ifNone: [^true].
^false! !
!GrammarProduction methodsFor: 'printing'!
printOn: aStream
self printSymbol: self leftHandSide on: aStream.
aStream
tab;
nextPut: $:;
space.
self rightHandSide do:
[:sym |
self printSymbol: sym on: aStream.
aStream space]! !
!GrammarProduction methodsFor: 'private'!
lr0ItemClass
^LR0Item!
lr1ItemClass
^LR1Item!
lrParserStateClass
^LRParserState!
printSymbol: sym on: aStream
"Render the given grammar symbol (terminal or nonterminal) on aStream.
This is provided so that grammars are printed in T-gen specification form.
Nonterminals and token class terminals are printed without #s or 's and
terminals are printed as strings."
(sym isNonterminal or: [sym isTokenClassTerminal])
ifTrue: [sym do: [:ch | aStream nextPut: ch]]
ifFalse: [sym printOn: aStream]!
symbolSuffixSeparatorChar
^self lrParserStateClass symbolSuffixSeparatorChar! !
!GrammarProduction methodsFor: 'conversion'!
asInitialLR0Item
^self lr0ItemClass
leftHandSide: self leftHandSide
preDotSymbols: OrderedCollection new
postDotSymbols: self rightHandSide copy!
asInitialLR1ItemWithLookahead: terminal
^self lr1ItemClass
leftHandSide: self leftHandSide
preDotSymbols: OrderedCollection new
postDotSymbols: self rightHandSide copy
lookahead: terminal!
asNonLalrSuffixedProduction
"Assuming I am of the form 'A.<stuff1>* -> B.<stuff2>* C.<stuff3>*',
answer the prefix production 'A -> B C'."
| separator lhs rhs |
separator := self symbolSuffixSeparatorChar.
lhs := self leftHandSide copyUpTo: separator.
rhs := self rightHandSide collect: [:sym | sym copyUpTo: separator].
^self species leftHandSide: lhs rightHandSide: rhs! !
!GrammarProduction methodsFor: 'first/follow sets'!
computeFirstIn: grammar using: graph
"Build dependency graph for first sets and initialize first sets. Starting at the left
end of my right hand side, symbols are processed until a terminal or non-nullable
nonterminal is encountered. Any terminal encountered is added to the first set
associated with my left hand side node in the graph. Any nonterminal
encountered means that I must include its first set in mine. This accomplished
(indirectly) by adding an edge in the graph from the nonterminal's node to my lhs
node. The actual first set unioning will be done after the graph is complete (see
sender)."
self rightHandSide do:
[:sym |
sym isTerminal
ifTrue:
[graph addTerminal: sym toNodeLabeled: self leftHandSide.
^self].
graph addEdgeFromNodeLabeled: sym toNodeLabeled: self leftHandSide.
(grammar isNullable: sym)
ifFalse: [^self]]!
computeFollowIn: grammar using: graph
"Build dependency graph for follow sets and initialize follow sets. This method
performs two distinct parts of the algorithm. First, each nonterminal in my right
hand side is checked to what symbols can follow it. Those symbols are added to
the follow set for the nonterminal's graph node. Second, starting at the right end
of my right hand side, symbols are processed until a terminal or non-nullable
nonterminal is encountered. Any nonterminal encountered means that my follow
set should also be included in its follow set. This accomplished (indirectly) by
adding an edge in the graph from my lhs node to the nonterminal's node. The
actual follow set unioning will be done after the graph is complete (see sender)."
| n currSym more j nextSym |
n := self rightHandSide size.
1 to: n - 1 do: [:i | (currSym := self rightHandSide at: i) isNonterminal
ifTrue:
[more := true.
j := i + 1.
[j <= n & more]
whileTrue:
[nextSym := self rightHandSide at: j.
(grammar firstSetOf: nextSym)
do: [:sym | graph addTerminal: sym toNodeLabeled: currSym].
j := j + 1.
more := grammar isNullable: nextSym]]].
self rightHandSide
reverseDo:
[:sym |
sym isTerminal ifTrue: [^self].
graph addEdgeFromNodeLabeled: self leftHandSide toNodeLabeled: sym.
(grammar isNullable: sym)
ifFalse: [^self]]! !
!GrammarProduction methodsFor: 'comparing'!
= aProd
^aProd isGrammarProduction
ifTrue: [self leftHandSide = aProd leftHandSide and: [self rightHandSide = aProd rightHandSide]]
ifFalse: [false]!
hash
"This is redefined because = is redefined."
^self leftHandSide hash bitXor: self rightHandSide hash! !
!GrammarProduction methodsFor: 'reconstructing'!
constructItsContentOn: aStream using: tokenTable
"Emit lhs and #( rhs ) on aStream"
(tokenTable indexOf: self leftHandSide)
reconstructOn: aStream.
aStream
space;
poundSign;
leftParenthesis.
self rightHandSide do:
[:ea |
(tokenTable indexOf: ea)
reconstructOn: aStream.
aStream space].
aStream rightParenthesis!
reconstructOn: aStream
"Emit #( productions ) on aStream "
aStream poundSign; leftParenthesis.
(self symbolTable at: self leftHandSide)
reconstructOn: aStream.
aStream
space;
poundSign;
leftParenthesis.
self rightHandSide do:
[:ea |
(self symbolTable at: ea)
reconstructOn: aStream.
aStream space].
aStream
rightParenthesis;
rightParenthesis;
space!
reconstructOn: aStream using: tokenTable
aStream poundSign; leftParenthesis.
self constructItsContentOn: aStream using: tokenTable.
aStream rightParenthesis; space! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
GrammarProduction class
instanceVariableNames: ''!
!GrammarProduction class methodsFor: 'instance creation'!
leftHandSide: arg1 rightHandSide: arg2
| newMe |
newMe := self new.
newMe leftHandSide: arg1.
newMe rightHandSide: arg2.
^newMe! !
Array variableSubclass: #Stack
instanceVariableNames: 'topPtr '
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Scanning/Parsing'!
Stack comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
This class provides a more traditional push/pop interface for Arrays.'!
!Stack methodsFor: 'private'!
copyEmpty: aSize
"Answer a copy of the receiver that contains no elements.
This method should be redefined in subclasses that add
instance variables, so that the state of those variables
is preserved"
^(super copyEmpty: aSize) topPtr: self topPtr.! !
!Stack methodsFor: 'state accessing'!
topPtr
^topPtr!
topPtr: arg
topPtr := arg! !
!Stack methodsFor: 'testing'!
isEmpty
^topPtr = 0!
isFull
^ topPtr = self basicSize! !
!Stack methodsFor: 'accessing'!
pop
"Answer the object on top of the stack."
| n |
n := self at: topPtr.
topPtr := topPtr - 1.
^n!
pop: numElem
"Pop and discard top numElems and answer receiver"
topPtr := topPtr - numElem!
push: anObject
"Push anObject onto the top of the stack."
self isFull ifTrue: [self grow].
topPtr := topPtr + 1.
^self at: topPtr put: anObject!
size
"Answer the number of objects on the stack."
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -