⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 collections-graphnodes.st

📁 編譯器的語法產生器
💻 ST
📖 第 1 页 / 共 2 页
字号:
Object subclass: #TreeNode
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Collections-Graph Nodes'!
TreeNode comment:
'=================================================
    Copyright (c) 1992 by Justin O. Graver.
    All rights reserved (with exceptions).
    For complete information evaluate "Object tgenCopyright."
=================================================

This abstract class provides the framework for both destructive and non-destructive tree traversals in which references to locally global objects are available without being explicitly passed as arguments.

Concrete subclasses must implement methods for traversing

	childrenDo:
		"Evaluate the argument block with each of my children."

	updateChildrenUsing:
		"Replace my children with the result of evaluating the argument block with the corresponding child."'!


!TreeNode methodsFor: 'traversing'!

childrenDo: aBlock
	"Evaluate aBlock for each of my children.
	This message should be reimplemented by my subclasses."

	^self		"default"!

preorderDo: preBlock updateUsing: postBlock 
	"Perform a traversal on myself and my children.  The preBlock is
	evaluated when first entering a node.  My children are replaced
	with the results of the traversal.  Thus, this message can be used
	to generate objects or alter my structure, whereas postorderDo:
	can only be used to examine my structure.  This message may be
	used in the following manner. 
	 
	a := aMethodNode
		preorderDo: [:node | node msg1]
		updateUsing: [:node | node msg2: globalRef]"

	preBlock value: self.
	self updateChildrenUsing: [:child | child preorderDo: preBlock updateUsing: postBlock].
	^postBlock value: self!

updateChildrenUsing: aBlock
	"Replace my children according to the value of aBlock.
	This message should be reimplemented by my subclasses."

	^self		"default"!

updateCopyUsing: aBlock 
	"Perform a postorder traversal on a copy of myself and
	my children, replacing my children with the results of the traversal. 
	Thus, this message can be used to generate objects or alter 
	my structure, whereas postorderDo: can only be used to examine 
	my structure.  This message may be used in the following manner. 
	 
	a := aMethodNode updateCopyUsing: [:node | node msg: globalRef]"

	| newNode |
	newNode := self copy.
	newNode updateChildrenUsing: [:child | child updateCopyUsing: aBlock].
	^aBlock value: newNode!

updateUsing: aBlock 
	"Perform a postorder traversal on myself and my children, 
	replacing my children with the results of the traversal. 
	Thus, this message can be used to generate objects or alter 
	my structure, whereas postorderDo: can only be used to examine 
	my structure.  This message may be used in the following manner. 
	 
	a := aMethodNode updateUsing: [:node | node msg: globalRef]"

	self updateChildrenUsing: [:child | child updateUsing: aBlock].
	^aBlock value: self! !

!TreeNode methodsFor: 'copying'!

copyTree
	"Answer a copy of this tree."

	^self copy updateChildrenUsing: [:child | child copyTree]! !

!TreeNode methodsFor: 'enumerating'!

postorderDo: aBlock
	"Perform a postorder traversal on myself and my children.
	This message may be used for examining the nodes of a tree
	for the purpose of gathering data or altering data fields.
	To alter the structure of the tree see traverseDo:.  One of
	the main advantages of this message is that it allows all nodes
	of the tree 'global' access to objects referenced in aBlock.
	Before, such arguments had to be passed explitely as arguments.
	This message may be used as follows.

	aMethodNode postorderDo: [:node | node enc: encoder root: self]"

	self childrenDo: [:child | child postorderDo: aBlock].
	aBlock value: self!

preorderDo: preBlock postorderDo: postBlock 
	"Perform a traversal on myself and my children.  The preBlock is 
	evaluated when entering a node and postBlock is evaluated just before 
	leaving.  See comment in postorderDo:."

	preBlock value: self.
	self childrenDo: [:child | child preorderDo: preBlock postorderDo: postBlock].
	postBlock value: self! !

Object subclass: #GraphNode
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Collections-Graph Nodes'!
GraphNode comment:
'=================================================
    Copyright (c) 1992 by Justin O. Graver.
    All rights reserved (with exceptions).
    For complete information evaluate "Object tgenCopyright."
=================================================

I am an abstract class of graph nodes.'!


GraphNode subclass: #DirectedGraphNode
	instanceVariableNames: 'predecessors '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Collections-Graph Nodes'!
DirectedGraphNode comment:
'=================================================
    Copyright (c) 1992 by Justin O. Graver.
    All rights reserved (with exceptions).
    For complete information evaluate "Object tgenCopyright."
=================================================

I maintain a collection of my predecessor nodes.

Instance Variables:
	predecessors		<OrderedCollection of: DirectedGraphNode>'!


!DirectedGraphNode methodsFor: 'state accessing'!

predecessors

	^predecessors!

predecessors: argument 

	predecessors := argument! !

!DirectedGraphNode methodsFor: 'initialization'!

init

	self predecessors: OrderedCollection new! !

!DirectedGraphNode methodsFor: 'modifying'!

addPredecessor: node 

	self predecessors add: node!

removePredecessor: node 

	self predecessors remove: node ifAbsent: [self error: 'precedessor not found']!

removePredecessor: node ifAbsent: aBlock 

	self predecessors remove: node ifAbsent: [^aBlock value]! !

!DirectedGraphNode methodsFor: 'enumerating'!

predecessorsDo: aBlock 
	"Evaluate aBlock with each of my predecessors."

	self predecessors do: aBlock! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

DirectedGraphNode class
	instanceVariableNames: ''!


!DirectedGraphNode class methodsFor: 'instance creation'!

new

	^super new init! !

DirectedGraphNode subclass: #NodeLabeledDigraphNode
	instanceVariableNames: 'label '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Collections-Graph Nodes'!
NodeLabeledDigraphNode comment:
'=================================================
    Copyright (c) 1992 by Justin O. Graver.
    All rights reserved (with exceptions).
    For complete information evaluate "Object tgenCopyright."
=================================================

I add labels to my nodes.  Node labels are assumed to be unique (see LabeledDigraph) although hashing and such is still done based on the node itself.

Instance Variables:
	label	<String>'!


!NodeLabeledDigraphNode methodsFor: 'state accessing'!

label

	^label!

label: argument 

	label := argument! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

NodeLabeledDigraphNode class
	instanceVariableNames: ''!


!NodeLabeledDigraphNode class methodsFor: 'instance creation'!

label: arg1 

	| newMe |
	newMe := self new.
	newMe label: arg1.
	^newMe! !

GraphNode subclass: #EdgeLabeledDigraphNode
	instanceVariableNames: 'edgeLabelMap '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Collections-Graph Nodes'!
EdgeLabeledDigraphNode comment:
'=================================================
    Copyright (c) 1992 by Justin O. Graver.
    All rights reserved (with exceptions).
    For complete information evaluate "Object tgenCopyright."
=================================================

I represent a node in an edge-labeled digraph.

Instance Variables:

	edgeLabelMap		<SetDictionary from: labels to: successors>'!


!EdgeLabeledDigraphNode methodsFor: 'accessing'!

successors

	^self edgeLabelMap elements! !

!EdgeLabeledDigraphNode methodsFor: 'state accessing'!

edgeLabelMap

	^edgeLabelMap!

edgeLabelMap: argument 

	edgeLabelMap := argument! !

!EdgeLabeledDigraphNode methodsFor: 'initialization'!

init

	self edgeLabelMap: SetDictionary new! !

!EdgeLabeledDigraphNode methodsFor: 'enumerating'!

successorsDo: aBlock 

	self successors do: aBlock!

successorsExceptSelfDo: aBlock 

	(self successors reject: [:succ | succ = self])
		do: aBlock! !

!EdgeLabeledDigraphNode methodsFor: 'modifying'!

addSuccessor: node withEdgeLabeled: label 

	self edgeLabelMap at: label add: node! !

!EdgeLabeledDigraphNode methodsFor: 'printing'!

printOn: aStream 

	self hash printOn: aStream.
	aStream nextPutAll: ': '; crtab.
	self edgeLabelMap
		associationsDo: 
			[:assoc | 
			assoc key printOn: aStream.
			aStream nextPutAll: ' ==> '.
			assoc value hash printOn: aStream.
			aStream crtab]! !

!EdgeLabeledDigraphNode methodsFor: 'converting'!

spaceOptimizeMap
	"Assumes self edgeLabelMap isDeterministic. 
	Note: doing this will dissable the messages #successors, 
	#addSuccessor:withEdgeLabeled:, and any senders of them, 
	since they assume a SetDictionary."

	self edgeLabelMap: self edgeLabelMap asDictionary! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

EdgeLabeledDigraphNode class
	instanceVariableNames: ''!


!EdgeLabeledDigraphNode class methodsFor: 'instance creation'!

new

	^super new init! !

EdgeLabeledDigraphNode subclass: #FSAState
	instanceVariableNames: 'stateID '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Collections-Graph Nodes'!
FSAState comment:
'=================================================
    Copyright (c) 1992 by Justin O. Graver.
    All rights reserved (with exceptions).
    For complete information evaluate "Object tgenCopyright."
=================================================

I am a general state in a finite state automata.'!


!FSAState methodsFor: 'state accessing'!

stateID

	^stateID!

stateID: id 

	stateID := id! !

!FSAState methodsFor: 'testing'!

hasStateID

	^self stateID notNil! !

!FSAState methodsFor: 'building'!

goto: aState on: transitionSymbol 

	self addSuccessor: aState withEdgeLabeled: transitionSymbol! !

!FSAState methodsFor: 'private'!

collectStatesIn: stateSet 
	"Add myself and all states reachable from me to stateSet. 
	If I'm the start state of an fsa then all my states are added."

	(stateSet includes: self)
		ifFalse: 
			[stateSet add: self.
			self successorsExceptSelfDo: [:succ | succ collectStatesIn: stateSet]]!

dfsaFinalStateClass

	^FSAFinalState!

dfsaStateClass

	^FSAState!

endOfInputToken
	"Answer a token representing the end of the input."

	^Character endOfInput!

epsilon
	"Answer an object used to represent the empty string (epsilon)."

	^EpsilonNode epsilon!

newDFSAStateFor: multiState 
	"Answer a new dfsa state that will represent the argument, a collection of states. 
	Make sure to transfer any final state information to the new state."

	| newFinalState finalStates |
	(finalStates := multiState select: [:state | state isFSAFinalState]) isEmpty
		ifTrue: [^self dfsaStateClass new]
		ifFalse: 
			[newFinalState := self dfsaFinalStateClass new.
			finalStates do: 
				[:fs | 
				fs literalTokens do: [:lit | newFinalState addLiteralToken: lit].
				fs tokenClasses do: [:tc | newFinalState addTokenClass: tc]].
			^newFinalState]!

nilOutStateIDs
	"Set my stateID to nil, likewise with all my successors."

	self stateID notNil
		ifTrue:
			[self stateID: nil.
			self successorsDo: [:succ | succ nilOutStateIDs]]!

partitionTransitionMapClass

	^PartitionTransitionMap!

stateSetClass

	^ItemSet! !

!FSAState methodsFor: 'removing nondeterminism'!

asDeterministicFSA
	"Answer a new deterministic version of myself. 
	
	Based on Algorithm 3.1 from 'Principles of Compiler Design', 
	by Aho and Ullman, 1977."

	| multiStateMap unprocessedStates newStartState currState ch transitStates multiState epsilonClosures newMultiState newState |
	epsilonClosures := self computeEpsilonClosures.
	multiStateMap := Dictionary new.
	unprocessedStates := Set new.
	newStartState := self newDFSAStateFor: (epsilonClosures at: self).
	multiStateMap at: (epsilonClosures at: self)

⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -