📄 t-gen-support.st
字号:
buildGrammarFrom: anArray
| newGrammar |
newGrammar := self new.
newGrammar productions: OrderedCollection new.
anArray do: [:prod | prod size = 3
ifTrue: [newGrammar productions add: (TransductionGrammarProduction
leftHandSide: (prod at: 1)
rightHandSide: (prod at: 2) asOrderedCollection
translationSymbol: (prod at: 3))]
ifFalse: [prod size = 2
ifTrue: [newGrammar productions add: (GrammarProduction leftHandSide: (prod at: 1)
rightHandSide: (prod at: 2) asOrderedCollection)]
ifFalse: [self error: 'wrong sized production array']]].
newGrammar startSymbol: ((anArray at: 1)
at: 1).
newGrammar init.
^newGrammar!
buildGrammarWithProductions: prods
"Assume that the left-hand side of the first production is the start symbol."
^self buildGrammarWithProductions: prods startSymbol: prods first leftHandSide!
buildGrammarWithProductions: prods startSymbol: aSymbol
| newGrammar |
newGrammar := self new.
newGrammar productions: prods.
newGrammar startSymbol: aSymbol.
newGrammar init.
^newGrammar! !
Set variableSubclass: #ItemSet
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Support'!
ItemSet comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
ItemSets are equal if they contain equal elements.'!
!ItemSet methodsFor: 'testing'!
isItemSet
^true! !
!ItemSet methodsFor: 'comparing'!
= anItemSet
^anItemSet isItemSet
ifTrue: [self size = anItemSet size and: [self size = (self union: anItemSet) size]]
ifFalse: [false]!
hash
"Make sure equal sets hash equally."
"A good and fast hashing function will require some more thought. I used to use
'self size bitXor: self first hash' but there is no guarantee that the first's of
equal sets will be the same element (even if their basicSizes are the same, due
to the temporal ordering of hash collisions). If simply 'size' doesn't give
reasonable performance, then try 'self inject: 0 into: [:max :each
| max max: each hash]'."
^self isEmpty
ifTrue: [151515]
ifFalse: [self size]! !
LR0Item variableSubclass: #LR1Item
instanceVariableNames: 'lookahead '
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Support'!
LR1Item comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I associate a lookahead symbol with a context-free grammar production with a ''dot'' somewhere in the right hand side. I''m used in the construction of LR(1) parsers.
leftHandSide -> <preDotSymbols> . <postDotSymbols> : <lookahead> => <translationSymbol>
Instance Variables:
lookahead <Symbol>'!
!LR1Item methodsFor: 'state accessing'!
lookahead
^lookahead!
lookahead: argument
lookahead := argument! !
!LR1Item methodsFor: 'testing'!
isLR1Item
^true! !
!LR1Item methodsFor: 'comparing'!
= anItem
^anItem isLR1Item
ifTrue: [self lookahead = anItem lookahead and: [super = anItem]]
ifFalse: [false]!
hash
"This is redefined because = is redefined."
^(self leftHandSide hash bitXor: self lookahead hash)
bitXor: (self preDotSymbols hash bitXor: self postDotSymbols hash)! !
!LR1Item methodsFor: 'accessing'!
lookaheadTail
"For an lr1 item 'B -> <alpha> . A <beta> : lookahead' answer
the string '<beta> lookahead'."
| string |
string := self postDotSymbols copy.
string removeFirst.
string addLast: self lookahead.
^string! !
!LR1Item methodsFor: 'printing'!
printOn: aStream
super printOn: aStream.
aStream nextPutAll: ': '.
self lookahead printOn: aStream! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
LR1Item class
instanceVariableNames: ''!
!LR1Item 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)
lookahead: self endOfInputSymbol!
leftHandSide: arg1 preDotSymbols: arg2 postDotSymbols: arg3 lookahead: arg4
| newMe |
newMe := self new.
newMe leftHandSide: arg1.
newMe preDotSymbols: arg2.
newMe postDotSymbols: arg3.
newMe lookahead: arg4.
^newMe!
leftHandSide: arg1 preDotSymbols: arg2 postDotSymbols: arg3 lookahead: arg4 translationSymbol: arg5
| newMe |
newMe := self new.
newMe leftHandSide: arg1.
newMe preDotSymbols: arg2.
newMe postDotSymbols: arg3.
newMe lookahead: arg4.
newMe translationSymbol: arg5.
^newMe! !
Object subclass: #PartitionTransitionMap
instanceVariableNames: 'partition transitionMap '
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Support'!
PartitionTransitionMap comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I am a partition-based transition map for an ordinary fsa state. I am used as an intermediate computational object in the dfsa minimization algorithm (see #asMinimalDFSA in class FiniteStateAutomata). My responsibilities include adding new partition-based transitions and testing for transition map equivalence.
Instance Variables:
partition <Partition> - the partition for the super state that I represent.
transitionMap <Dictionary from: (transition symbol) to: Partition>
where <Partition> = <Set of: (FSAState + FSAFinalState)>'!
!PartitionTransitionMap methodsFor: 'state transitions'!
goto: aPartition on: aSymbol
(self transitionMap includesKey: aSymbol)
ifTrue: [self error: 'these are supposed to be deterministic, what gives?'].
self transitionMap at: aSymbol put: aPartition! !
!PartitionTransitionMap methodsFor: 'state accessing'!
partition
^partition!
partition: argument
partition := argument!
transitionMap
^transitionMap!
transitionMap: argument
transitionMap := argument! !
!PartitionTransitionMap methodsFor: 'initialization'!
initWithPartition: pt
self transitionMap: Dictionary new.
self partition: pt! !
!PartitionTransitionMap methodsFor: 'testing'!
isPartitionTransitionMap
^true! !
!PartitionTransitionMap methodsFor: 'comparing'!
hasSameTransitionMapAs: aPTMap
"Two partition transition maps are equivalent if they have equivalent transition maps."
| map1 map2 keys1 keys2 values1 values2 |
^aPTMap isPartitionTransitionMap
ifTrue:
["First, check map sizes."
map1 := self transitionMap.
map2 := aPTMap transitionMap.
map1 size ~= map2 size ifTrue: [^false].
"Next, check map domain sizes."
keys1 := map1 keys.
keys2 := map2 keys.
keys1 size ~= (keys1 union: keys2) size ifTrue: [^false].
"Last, check map range sizes."
values1 := map1 valuesAsSet.
values2 := map2 valuesAsSet.
values1 size ~= (values1 union: values2) size ifTrue: [^false].
^true]
ifFalse: [false]! !
!PartitionTransitionMap methodsFor: 'printing'!
printOn: aStream
aStream nextPutAll: self partition hash printString; cr.
self transitionMap printOn: aStream! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
PartitionTransitionMap class
instanceVariableNames: ''!
!PartitionTransitionMap class methodsFor: 'instance creation'!
forPartition: pt
^self new initWithPartition: pt! !
LabeledDigraph variableSubclass: #FirstFollowGraph
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Support'!
FirstFollowGraph comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I am a graph consisting of FirstFollowGraphNodes used in the computation of first and follow sets. I serve as the public interface to my nodes.'!
!FirstFollowGraph methodsFor: 'accessing'!
nodeSetMap
"Answer a map from node names (nonterminals) to sets of terminals, representing
either the first or follow sets."
| map |
map := SetDictionary new.
self nodesDo: [:node | map add: node asAssociation].
^map! !
!FirstFollowGraph methodsFor: 'modifying'!
addTerminal: term toNodeLabeled: label
(self detect: [:node | node label = label])
addTerminal: term! !
!FirstFollowGraph methodsFor: 'first/follow sets'!
propagateSetUnions
"For each of my nodes, replace its node set with the union of its old node set
and the node sets along all incoming edges. Repeat until no more changes."
| changes |
changes := true.
[changes]
whileTrue: [changes := self inject: false into: [:chngs :node | chngs | node unionWithPredecessorsChangesMe]]! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
FirstFollowGraph class
instanceVariableNames: ''!
!FirstFollowGraph class methodsFor: 'instance creation'!
preferredNodeClass
^FirstFollowGraphNode! !
NodeLabeledDigraphNode subclass: #FirstFollowGraphNode
instanceVariableNames: 'terminals '
classVariableNames: ''
poolDictionaries: ''
category: 'T-gen-Support'!
FirstFollowGraphNode comment:
'=================================================
Copyright (c) 1992 by Justin O. Graver.
All rights reserved (with exceptions).
For complete information evaluate "Object tgenCopyright."
=================================================
I represent a nonterminal of a grammar for the purpose of first and follow set computation.
Instance Variables:
terminals <Set of: Symbols> - the first or follow set of my nonterminal.'!
!FirstFollowGraphNode methodsFor: 'first/follow sets'!
unionWithPredecessorsChangesMe
"Answer true if adding the terminals of my predecessors changes my terminals
and false otherwise."
| myTerms initialSize |
myTerms := self terminals.
initialSize := myTerms size.
self predecessorsDo: [:pred | myTerms addAll: pred terminals].
^initialSize ~= myTerms size! !
!FirstFollowGraphNode methodsFor: 'converting'!
asAssociation
^Association key: self label value: self terminals! !
!FirstFollowGraphNode methodsFor: 'adding'!
addTerminal: term
self terminals add: term! !
!FirstFollowGraphNode methodsFor: 'initialization'!
init
super init.
self terminals: Set new! !
!FirstFollowGraphNode methodsFor: 'state accessing'!
terminals
^terminals!
terminals: argument
terminals := argument! !
Grammar initialize!
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -