📄 t-gen-scanningparsing.st
字号:
^topPtr!
top
"Answer (without removing) the object on top of the stack."
^self at: topPtr! !
!Stack methodsFor: 'initialization'!
init
self topPtr: 0! !
!Stack methodsFor: 'enumerating'!
do: aBlock
"Evaluate aBlock for each object on the stack, from top to bottom."
^super reverseDo: aBlock!
reverseDo: aBlock
"Evaluate aBlock for each object on the stack, from bottom to top."
^super do: aBlock! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
Stack class
instanceVariableNames: ''!
!Stack class methodsFor: 'instance creation'!
new
^self new: 100!
new: arg
^( super new: arg ) init! !
Dictionary variableSubclass: #LLParserTable
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Scanning/Parsing'!
LLParserTable comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I implement a two dimensional LL(1) parser table with rows indexed by nonterminals, columns indexed by terminals, and with production table entries. At the top level I''m a Dictionary from nonterminals to rows; each row is a SetDictionary from terminals to productions. In deterministic tables (tables without multiple entries) the SetDictionaries can be (and are) converted into simple Dictionaries.'!
!LLParserTable methodsFor: 'testing'!
isDeterministic
self detect: [:row | row isDeterministic not]
ifNone: [^true].
^false! !
!LLParserTable methodsFor: 'private'!
newRow
^self rowClass new!
rowClass
^SetDictionary! !
!LLParserTable methodsFor: 'accessing'!
atNonterminal: nont andTerminal: term addProduction: prod
| row |
row := self at: nont ifAbsent: [self at: nont put: self newRow].
^row at: term add: prod!
productionAtNonterminal: nont andTerminal: term
| row |
row := self at: nont ifAbsent: [self raiseNoTransitionExceptionErrorString: 'illegal nonterminal symbol encountered: ' , nont].
^row at: term ifAbsent: [self raiseNoTransitionExceptionErrorString: 'expecting one of ' , row keys printString , ' but encountered: ''' , term , '''']! !
!LLParserTable methodsFor: 'converting'!
spaceOptimize
"Assumes self isDeterministic."
self associationsDo: [:assoc | self at: assoc key put: assoc value asDictionary]! !
!LLParserTable methodsFor: 'exception handling'!
raiseNoTransitionExceptionErrorString: aString
self class noTransitionSignal raiseErrorString: aString! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
LLParserTable class
instanceVariableNames: 'noTransitionSignal '!
!LLParserTable class methodsFor: 'state accessing'!
noTransitionSignal
^noTransitionSignal!
noTransitionSignal: argument
noTransitionSignal := argument! !
!LLParserTable class methodsFor: 'class initialization'!
initialize
"LLParserTable initialize"
self noTransitionSignal: (Signal new nameClass: self message: #noTransitionSymbol)! !
GrammarProduction variableSubclass: #TransductionGrammarProduction
instanceVariableNames: 'translationSymbol '
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Scanning/Parsing'!
TransductionGrammarProduction comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I add a translation attribute to context-free grammar productions so that I can be used to build simple transduction grammars (or syntax-directed translation scheme). Transduction grammars are used to build abstract syntax trees rather than derivation trees during parsing. For more information, refer to Chapter 7. ("Syntax-Directed Translation") in {\em Compiler Construction: Theory and Practice} by Barrett, Bates, Gustafson, and Couch.
Instance Variables:
translationSymbol <String> - used as basis for translation node when parsing.'!
!TransductionGrammarProduction methodsFor: 'state accessing'!
translationSymbol
^translationSymbol!
translationSymbol: argument
translationSymbol := argument! !
!TransductionGrammarProduction methodsFor: 'testing'!
hasTranslation
^true! !
!TransductionGrammarProduction methodsFor: 'printing'!
printOn: aStream
super printOn: aStream.
aStream nextPutAll: ' {'.
self printSymbol: self translationSymbol asSymbol on: aStream.
aStream nextPutAll: '} '! !
!TransductionGrammarProduction methodsFor: 'conversion'!
asInitialLR0Item
^self lr0ItemClass
leftHandSide: self leftHandSide
preDotSymbols: OrderedCollection new
postDotSymbols: self rightHandSide copy
translationSymbol: self translationSymbol!
asInitialLR1ItemWithLookahead: terminal
^self lr1ItemClass
leftHandSide: self leftHandSide
preDotSymbols: OrderedCollection new
postDotSymbols: self rightHandSide copy
lookahead: terminal
translationSymbol: self translationSymbol!
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
translationSymbol: self translationSymbol! !
!TransductionGrammarProduction methodsFor: 'private'!
epsilonSymbol
^#nil!
leftLiftSymbol
^#liftLeftChild!
rightLiftSymbol
^#liftRightChild! !
!TransductionGrammarProduction methodsFor: 'parse tree building'!
computeResultNodeFor: builder withArgNodes: nodes
"Three kinds of translation symbols are currently supported: node names, special
directives, and arbitrary message selectors. For a node name, a new instance of
the specified node is created and given nodes, if any, as its children. The special
directive 'nil' simply returns nil. The directive liftRightChild adds any nodes
preceeding the right-most node as children to the right-most node, and returns
the right-most node. The directive liftLeftChild works in an analogous fashion.
Arbitrary message selectors must take the number of arguments in nodes and
are invoked as a builder message, thus allowing users to define their own
tree-building messages."
| symbol node |
symbol := self translationSymbol asSymbol.
symbol first isUppercase ifTrue: [^nodes isEmpty
ifTrue: [builder makeNewNode: symbol]
ifFalse: [builder makeNewNode: symbol withChildren: nodes]].
symbol = self epsilonSymbol ifTrue: [^builder answerNil].
symbol = self rightLiftSymbol
ifTrue:
[nodes size < 2 ifTrue: [self error: 'Only use liftRightChild when there are at least two right-hand-side nonterminals.'].
"special case for building lists ending with epsilon"
(nodes size = 2 and: [nodes last isNil])
ifTrue: [^builder answerArgument: nodes first].
node := nodes removeLast.
^builder addChildrenFirst: nodes to: node].
symbol = self leftLiftSymbol
ifTrue:
[nodes size < 2 ifTrue: [self error: 'Only use liftLeftChild when there are at least two right-hand-side nonterminals.'].
"special case for building lists beginning with epsilon"
(nodes size = 2 and: [nodes first isNil])
ifTrue: [^builder answerArgument: nodes last].
node := nodes removeFirst.
^builder addChildrenLast: nodes to: node].
symbol numArgs = nodes size ifFalse: [self error: 'Translation message selectors must have the same number of arguments as right-hand-side nonterminals.'].
nodes isEmpty ifTrue: [^builder perform: symbol].
"It may be more efficient to check the number of arguments and use
perform:with:, etc., but probably not."
^builder perform: symbol withArguments: nodes asArray!
computeResultNodeFor: builder withTokenClassValue: value
"I am assumed to be a production of the form 'A -> <tc> => symbol'.
The symbol can be either a node name or a one-argument message selector.
If it is a node name then create a new instance of that node with the specified
attribute value. If it is a message selector then invoke the corresponding
operation on the builder with the specified value."
| symbol |
symbol := self translationSymbol asSymbol.
symbol first isUppercase
ifTrue: [^builder makeNewNode: symbol withAttribute: value]
ifFalse: [symbol numArgs = 1
ifTrue: [^builder perform: symbol with: value]
ifFalse: [self error: 'Expected either a node name or a one argument
message selector as a translation symbol.']]! !
!TransductionGrammarProduction methodsFor: 'reconstructing'!
constructItsContentOn: aStream using: tokenTable
"Emit lhs , #( rhs ) and translationSymbol on aStream"
super constructItsContentOn: aStream using: tokenTable.
(tokenTable indexOf: self translationSymbol)
reconstructOn: aStream! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
TransductionGrammarProduction class
instanceVariableNames: ''!
!TransductionGrammarProduction class methodsFor: 'instance creation'!
leftHandSide: arg1 rightHandSide: arg2 translationSymbol: arg3
| newMe |
newMe := self new.
newMe leftHandSide: arg1.
newMe rightHandSide: arg2.
newMe translationSymbol: arg3.
^newMe! !
Object subclass: #TokenTypeActionHolder
instanceVariableNames: 'type action '
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Scanning/Parsing'!
TokenTypeActionHolder comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I am used to package token type and actions together for transport between FSAFinalStates and the scanner.
Instance Variables:
type <String> - token type.
action <Symbol + UndefinedObject> - a message selector that will be sent to the scanner (via #perform:) when a token with this type is recognized.'!
!TokenTypeActionHolder methodsFor: 'state accessing'!
action
^action!
action: argument
action := argument!
type
^type!
type: argument
type := argument! !
!TokenTypeActionHolder methodsFor: 'printing'!
printOn: aStream
aStream nextPutAll: self type.
aStream nextPutAll: ' : {'.
aStream nextPutAll: self action.
aStream nextPutAll: '} ;'! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
TokenTypeActionHolder class
instanceVariableNames: ''!
!TokenTypeActionHolder class methodsFor: 'instance creation'!
type: arg1 action: arg2
| newMe |
newMe := self new.
newMe type: arg1.
newMe action: arg2.
^newMe! !
LRParserState initialize!
LLParserTable initialize!
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -