📄 t-gen-grammarnodes.st
字号:
ParseTreeNode subclass: #GrammarParseTreeNode
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Grammar Nodes'!
GrammarParseTreeNode comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
This class is an abstract class for grammar parse tree nodes.'!
!GrammarParseTreeNode methodsFor: 'private'!
alternationNodeClass
^AlternationNode!
concatenationNodeClass
^ConcatenationNode! !
!GrammarParseTreeNode methodsFor: 'building parse trees'!
alternateWith: node
^node alternateWithNonAltNode: self!
alternateWithAltNode: node
node children addLast: self.
^node!
alternateWithNonAltNode: node
^self alternationNodeClass children: (OrderedCollection with: node with: self)!
concatenateWith: node
^node concatenateWithNonCatNode: self!
concatenateWithCatNode: node
node children addLast: self.
^node!
concatenateWithNonCatNode: node
^self concatenationNodeClass children: (OrderedCollection with: node with: self)! !
GrammarParseTreeNode subclass: #ProductionNode
instanceVariableNames: 'leftHandSide rightHandSides '
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Grammar Nodes'!
ProductionNode comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I am a grammar production.
Instance Variables:
leftHandSide <NonterminalNode>
rightHandSides <OrderedCollection> - rhs''s for productions of the form A -> x | y | z.'!
!ProductionNode methodsFor: 'state accessing'!
leftHandSide
^leftHandSide!
leftHandSide: argument
leftHandSide := argument!
rightHandSides
^rightHandSides!
rightHandSides: argument
rightHandSides := argument! !
!ProductionNode methodsFor: 'building parse trees'!
addChildrenInitial: anOrderedCollection
self leftHandSide: anOrderedCollection removeFirst.
self rightHandSides: anOrderedCollection removeFirst! !
!ProductionNode methodsFor: 'traversing'!
childrenDo: aBlock
"Evaluate aBlock for each of my children."
aBlock value: self leftHandSide.
self rightHandSides do: aBlock!
updateChildrenUsing: aBlock
"Replace my children according to the value of aBlock."
self leftHandSide: (aBlock value: self leftHandSide).
self rightHandSides: (self rightHandSides collect: aBlock)! !
!ProductionNode methodsFor: 'printing'!
printOn: aStream
self leftHandSide printOn: aStream.
aStream nextPutAll: ' : '.
self rightHandSides do:
[:rhs |
rhs printOn: aStream.
aStream
cr;
tab;
nextPut: $|.
aStream cr]! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
ProductionNode class
instanceVariableNames: ''!
!ProductionNode class methodsFor: 'instance creation'!
leftHandSide: lhs rightHandSides: rhs
| newNode |
newNode := self new.
newNode leftHandSide: lhs.
newNode rightHandSides: rhs.
^newNode! !
GrammarParseTreeNode subclass: #GrammarLeafNode
instanceVariableNames: 'symbol '
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Grammar Nodes'!
GrammarLeafNode comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I am an abstract class for grammar tree leaf nodes.
Instance Variables:
symbol <Symbol + String> - a terminal, nonterminal, or transduction symbol.'!
!GrammarLeafNode methodsFor: 'state accessing'!
symbol
^symbol!
symbol: argument
symbol := argument! !
!GrammarLeafNode methodsFor: 'building parse trees'!
setAttribute: value
self symbol: value! !
!GrammarLeafNode methodsFor: 'printing'!
printOn: aStream
aStream nextPutAll: self symbol! !
!GrammarLeafNode methodsFor: 'transforming'!
needsTransforming
^false!
transformUsing: lhsNames withLHS: lhsNode alpha: alphaNodes gamma: gammaNodes
"Productions of the form 'A -> leaf' do not need transforming.
Signal this by answering an empty collection."
^OrderedCollection new! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
GrammarLeafNode class
instanceVariableNames: ''!
!GrammarLeafNode class methodsFor: 'instance creation'!
symbol: aSymbol
| newNode |
newNode := self new.
newNode symbol: aSymbol.
^newNode! !
GrammarLeafNode subclass: #TranslationNode
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Grammar Nodes'!
TranslationNode comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I hold a transduction node.'!
GrammarLeafNode subclass: #TerminalNode
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Grammar Nodes'!
TerminalNode comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I hold a terminal.'!
!TerminalNode methodsFor: 'converting'!
asGrammarSymbol
"Answer my symbol as a Terminal (String). A literal token is a string within a
string so trim the extra quotes."
| sym |
^(sym := self symbol) isTokenClassTerminal
ifTrue: [sym]
ifFalse: [sym copyFrom: 2 to: sym size - 1]! !
!TerminalNode methodsFor: 'testing'!
isTerminalNode
^true! !
!TerminalNode methodsFor: 'collecting'!
collectSymbol
| regexpr |
regexpr := OrderedCollection new.
regexpr add: self asGrammarSymbol.
^regexpr! !
ProductionNode subclass: #RRPGProductionNode
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Grammar Nodes'!
RRPGProductionNode comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I am an RRPG production.'!
!RRPGProductionNode methodsFor: 'printing'!
printOn: aStream
self leftHandSide printOn: aStream.
aStream nextPutAll: ' : '.
self rightHandSides printOn: aStream.
aStream nextPutAll: ' ; '; cr! !
!RRPGProductionNode methodsFor: 'converting'!
convertToCFGUsing: lhsNames
"Remove all RRPG grammar operators from my rhs and answer a
collection of CFG RRPGProductionNodes. This method recursively
decomposes productions into more primitive forms until no more
decomposition is possible (designated by an empty result from
transformUsing:)"
| prods resultProds |
resultProds := OrderedCollection new.
(prods := self transformUsing: lhsNames) isEmpty
ifTrue: [resultProds add: self]
ifFalse: [prods do: [:p | resultProds addAll: (p convertToCFGUsing: lhsNames)]].
^resultProds! !
!RRPGProductionNode methodsFor: 'transforming'!
transformUsing: lhsNames
"At this point there are two main cases to handle: a top-level
AlternationNode or an RRPGRightHandSideNode. AlternationNodes
are simply broken up into several RRPGProductionNodes.
RRPGRightHandSideNodes are transformed, if necessary. Pass along
my lhs so whole productions can be created by the rhs nodes."
^self rightHandSides transformUsing: lhsNames withLHS: self leftHandSide! !
GrammarLeafNode subclass: #NonterminalNode
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Grammar Nodes'!
NonterminalNode comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I hold a nonterminal.'!
!NonterminalNode methodsFor: 'converting'!
asGrammarSymbol
"Answer my symbol as a Nonterminal (Symbol)."
^self symbol asSymbol! !
!NonterminalNode methodsFor: 'collecting'!
collectSymbol
| regexpr |
regexpr := OrderedCollection new.
regexpr add: self asGrammarSymbol.
^regexpr! !
GrammarParseTreeNode subclass: #RightHandSideNode
instanceVariableNames: 'symbols translationSymbol '
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Grammar Nodes'!
RightHandSideNode comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
This class represents the right-hand side of a grammar rule.
Instance Variables
symbols <OrderedCollection> - rhs of production rule.
translationSymbol <Symbol> - symbol for transduction.'!
!RightHandSideNode methodsFor: 'state accessing'!
symbols
^symbols!
symbols: argument
symbols := argument!
translationSymbol
^translationSymbol!
translationSymbol: argument
translationSymbol := argument! !
!RightHandSideNode methodsFor: 'building parse trees'!
addChildrenInitial: anOrderedCollection
self symbols: anOrderedCollection removeFirst.
self translationSymbol: anOrderedCollection removeFirst! !
!RightHandSideNode methodsFor: 'traversing'!
childrenDo: aBlock
"Evaluate aBlock for each of my children."
self symbols do: aBlock.
aBlock value: self translationSymbol!
updateChildrenUsing: aBlock
"Replace my children according to the value of aBlock."
self symbols: (self symbols collect: aBlock).
self translationSymbol: (aBlock value: self translationSymbol)! !
!RightHandSideNode methodsFor: 'printing'!
printOn: aStream
self printSymbolsOn: aStream.
self translationSymbol notNil
ifTrue:
[aStream nextPut: ${.
self translationSymbol printOn: aStream.
aStream nextPutAll: '} ;']!
printSymbolsOn: aStream
self symbols do:
[:sym |
sym printOn: aStream.
aStream space]! !
!RightHandSideNode methodsFor: 'converting'!
asProductionWithLeftHandSide: lhs
"Answer the GrammarProduction I represent."
| rhs |
rhs := self convertSymbols.
^self translationSymbol isNil
ifTrue: [GrammarProduction leftHandSide: lhs rightHandSide: rhs]
ifFalse: [TransductionGrammarProduction
leftHandSide: lhs
rightHandSide: rhs
translationSymbol: self translationSymbol symbol]!
convertSymbols
^self symbols collect: [:sym | sym asGrammarSymbol]! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
RightHandSideNode class
instanceVariableNames: ''!
!RightHandSideNode class methodsFor: 'instance creation'!
symbols: arg1 translationSymbol: arg2
| newNode |
newNode := self new.
newNode symbols: arg1.
newNode translationSymbol: arg2.
^newNode! !
RightHandSideNode subclass: #RRPGRightHandSideNode
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Grammar Nodes'!
RRPGRightHandSideNode comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
This class represents the right hand side of an RRPG grammar production.
Instance Variables:
regexpr <RegularExpressionNode> - the rhs of an RRPG grammar production is a regular expression of grammar symbols.'!
!RRPGRightHandSideNode methodsFor: 'printing'!
printSymbolsOn: aStream
self symbols printOn: aStream! !
!RRPGRightHandSideNode methodsFor: 'converting'!
convertSymbols
^self symbols collectSymbol! !
!RRPGRightHandSideNode methodsFor: 'transforming'!
transformUsing: lhsNames withLHS: lhsNode
^self symbols
transformUsing: lhsNames
withLHS: lhsNode
alpha: OrderedCollection new
gamma: OrderedCollection new! !
GrammarParseTreeNode subclass: #GrammarNode
instanceVariableNames: 'productions '
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Grammar Nodes'!
GrammarNode comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I am the root of the grammar tree.
Instance Variables:
productions <OrderedCollection> - the productions of the grammar.'!
!GrammarNode methodsFor: 'traversing'!
childrenDo: aBlock
"Evaluate aBlock for each of my children."
^self productions do: aBlock!
updateChildrenUsing: aBlock
"Replace my children according to the value of aBlock."
^self productions: (self productions collect: aBlock)! !
!GrammarNode methodsFor: 'state accessing'!
productions
^productions!
productions: argument
productions := argument! !
!GrammarNode methodsFor: 'building parse trees'!
addChildrenFirst: anOrderedCollection
self productions addAllFirst: anOrderedCollection!
addChildrenInitial: anOrderedCollection
self productions addAll: anOrderedCollection! !
!GrammarNode methodsFor: 'initialization'!
init
self productions: OrderedCollection new! !
!GrammarNode methodsFor: 'printing'!
printOn: aStream
self productions do:
[:prod |
prod printOn: aStream.
aStream cr]! !
!GrammarNode methodsFor: 'converting'!
asContextFreeGrammar
"Answer the CFG representation of this RRPG grammar."
| transProds lhsNames baseProds |
transProds := OrderedCollection new.
lhsNames := Set new.
"Remove all RRPG grammar operators."
self childrenDo: [:prod | transProds addAll: (prod convertToCFGUsing: lhsNames)].
"Convert from parsetree format to grammar format."
baseProds := transProds
collect:
[:prod |
| lhs |
lhs := prod leftHandSide asGrammarSymbol.
prod rightHandSides asProductionWithLeftHandSide: lhs].
^Grammar buildGrammarWithProductions: baseProds! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
GrammarNode class
instanceVariableNames: ''!
!GrammarNode class methodsFor: 'instance creation'!
new
^super new init! !
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -