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

📄 t-gen-regularexpressionnodes.st

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

I am the root of a regular expression tree.'!


!RegularExpressionNode methodsFor: 'private'!

alternationNodeClass

	^AlternationNode!

characterNodeClass

	^CharacterNode!

concatenationNodeClass

	^ConcatenationNode!

createNewProductionWithLHS: lhsNode andRHS: anOrderedCollection 
	"Create a new RRPGProductionNode given its lhs and a collection of regular 
	expression nodes whose concatenation forms the rhs. Note: anOrderedCollection 
	may contain ConcatenationNodes which need to be 'expanded' to avoid nesting 
	within the ConcatenationNode created by this method. Since each transformation 
	is done individually (i.e. this method gets invoked each time a new production is 
	created), the CatenationNodes will never be nested more then one deep."

	| rhs rhsNode childNodes |
	rhs := anOrderedCollection isEmpty
				ifTrue: [self epsilonNodeClass new]
				ifFalse: [anOrderedCollection size = 1
						ifTrue: [anOrderedCollection first]
						ifFalse: 
							[childNodes := OrderedCollection new.
							anOrderedCollection do: [:node | node isConcatenationNode
									ifTrue: [childNodes addAllLast: node children]
									ifFalse: [childNodes addLast: node]].
							self concatenationNodeClass children: childNodes]].
	rhsNode := self rhsNodeClass symbols: rhs translationSymbol: nil.
	^self productionNodeClass leftHandSide: lhsNode rightHandSides: rhsNode!

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

	^self epsilonNodeClass epsilon!

epsilonNodeClass

	^EpsilonNode!

fsaFinalStateClass

	^FSAFinalState!

fsaStateClass

	^FSAState!

nameExtensionString
	"Answer a string appropriate for creating new nonterminals by suffixing."

	^'0'!

newNonterminal: lhsNode with: lhsNames 

	| lhs |
	lhs := lhsNode.
	lhsNames isEmpty
		ifTrue: [lhsNames add: lhs]
		ifFalse: 
			[[lhsNames includes: lhs]
				whileTrue: [lhs := lhs , '`'].
			lhsNames add: lhs].
	^NonterminalNode new setAttribute: lhs!

newNonterminalFrom: lhsNode excluding: lhsNames 
	"Answer a new nonterminal based on lhsNode that is
	not already in lhsNames."

	| newName |
	newName := lhsNode symbol.
	[newName := newName , self nameExtensionString.
	lhsNames includes: newName] whileTrue.
	lhsNames add: newName.
	^self nonterminalNodeClass symbol: newName!

nonterminalNodeClass

	^NonterminalNode!

productionNodeClass

	^RRPGProductionNode!

rhsNodeClass

	^RRPGRightHandSideNode!

starClosureNodeClass

	^StarClosureNode!

tokenClassificationClass

	^TokenClassification! !

!RegularExpressionNode methodsFor: 'converting'!

asDFSA

	| fsa |
	fsa := self asFSA.
	^fsa asDeterministicFSA!

asFSA

	| startState finalState |
	startState := self fsaStateClass new.
	finalState := self fsaFinalStateClass new.
	self asFSAStartingAt: startState endingAt: finalState.
	^startState!

asFSAStartingAt: startState endingAt: finalState 

	self subclassResponsibility!

asFSAWithLiteral: literal startingAt: startState 

	| finalState |
	"First, build main fsa."
	finalState := self fsaFinalStateClass new.
	self asFSAStartingAt: startState endingAt: finalState.
	finalState addLiteralToken: literal.
	^startState!

asFSAWithType: type andAction: action startingAt: startState 

	| finalState |
	"First, build main fsa."
	finalState := self fsaFinalStateClass new.
	self asFSAStartingAt: startState endingAt: finalState.
	finalState addTokenClass: (self tokenClassificationClass tokenType: type action: action).
	^startState!

asPureRegExpr
	"Answer a new version of the receiver consisting of only characters, 
	concatenations, alternations, and (star) closures. Also, eliminate single 
	child alternations and concatenations."

	^self		"default"!

minimize: recognizer 

	^recognizer asMinimalDFSA! !

!RegularExpressionNode methodsFor: 'traversing'!

addNonemptyLeavesTo: aSet 

	^self		"default is do nothing"!

collectNonemptyLeavesIn: aSet 

	self postorderDo: [:child | child addNonemptyLeavesTo: aSet]! !

!RegularExpressionNode methodsFor: 'transforming'!

needsTransforming

	^false! !

!RegularExpressionNode 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)! !

RegularExpressionNode subclass: #EpsilonNode
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'T-gen-Regular Expression Nodes'!
EpsilonNode comment:
'=================================================
    Copyright (c) 1992 by Justin O. Graver.
    All rights reserved (with exceptions).
    For complete information evaluate "Object tgenCopyright."
=================================================

I represent the empty regular expression.'!


!EpsilonNode methodsFor: 'building parse trees'!

concatenateWith: node

	^node!

concatenateWithCatNode: node

	^node!

concatenateWithNonCatNode: node

	^node! !

!EpsilonNode methodsFor: 'printing'!

printOn: aStream 

	aStream nextPutAll: '<epsilon>'! !

!EpsilonNode methodsFor: 'converting'!

asFSAStartingAt: startState endingAt: finalState 

	startState goto: finalState on: self epsilon! !

!EpsilonNode methodsFor: 'collecting'!

collectSymbol

	^OrderedCollection new! !

!EpsilonNode methodsFor: 'testing'!

isEpsilonNode

	^true! !

!EpsilonNode methodsFor: 'transforming'!

transformUsing: lhsNames withLHS: lhsNode alpha: alphaNodes gamma: gammaNodes
	"Productions of the form 'A -> <epsilon>' do not need transforming.
	Signal this by answering an empty collection."

	^OrderedCollection new! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

EpsilonNode class
	instanceVariableNames: ''!


!EpsilonNode class methodsFor: 'constants'!

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

	^Character endOfInput! !

RegularExpressionNode subclass: #BinaryRegExprNode
	instanceVariableNames: 'leftChild rightChild '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'T-gen-Regular Expression Nodes'!
BinaryRegExprNode comment:
'=================================================
    Copyright (c) 1992 by Justin O. Graver.
    All rights reserved (with exceptions).
    For complete information evaluate "Object tgenCopyright."
=================================================

I am a binary regular expression.

Instance Variables:

	leftChild	<RegExprNode>
	rightChild	<RegExprNode>'!


!BinaryRegExprNode methodsFor: 'building parse trees'!

addChildrenFirst: anOrderedCollection 

	anOrderedCollection size = 1
		ifTrue: [self leftChild: anOrderedCollection removeFirst]
		ifFalse: [self error: 'wrong  number of children']!

addChildrenInitial: anOrderedCollection 

	anOrderedCollection size = 2
		ifTrue: 
			[self leftChild: anOrderedCollection removeFirst.
			self rightChild: anOrderedCollection removeFirst]
		ifFalse: [anOrderedCollection size = 1
				ifTrue: [self rightChild: anOrderedCollection removeFirst]
				ifFalse: [self error: ' wrong  number of children']]! !

!BinaryRegExprNode methodsFor: 'state accessing'!

leftChild

	^leftChild!

leftChild: argument 

	leftChild := argument!

rightChild

	^rightChild!

rightChild: argument 

	rightChild := argument! !

!BinaryRegExprNode methodsFor: 'traversing'!

childrenDo: aBlock 
	"Evaluate aBlock for each of my children."

	aBlock value: self leftChild.
	aBlock value: self rightChild!

updateChildrenUsing: aBlock 
	"Replace my children according to the value of aBlock."

	self leftChild: (aBlock value: self leftChild).
	self rightChild: (aBlock value: self rightChild)! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

BinaryRegExprNode class
	instanceVariableNames: ''!


!BinaryRegExprNode class methodsFor: 'instance creation'!

leftChild: arg1 rightChild: arg2 

	| newMe |
	newMe := self new.
	newMe leftChild: arg1.
	newMe rightChild: arg2.
	^newMe! !

RegularExpressionNode subclass: #CharRangeNode
	instanceVariableNames: 'firstChar lastChar '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'T-gen-Regular Expression Nodes'!
CharRangeNode comment:
'=================================================
    Copyright (c) 1992 by Justin O. Graver.
    All rights reserved (with exceptions).
    For complete information evaluate "Object tgenCopyright."
=================================================

I represent the alternations of each atomic character in a range.  I.e. ''firstChar-lastChar'' = ''firstChar | ... | lastChar''.  I may only appear as a child of a AlternationRangeNode or a ComplementedAlternationRangeNode.

Instance Variables:
	firstChar	<CharacterNode>
	lastChar	<CharacterNode>'!


!CharRangeNode methodsFor: 'state accessing'!

firstChar

	^firstChar!

firstChar: argument 

	firstChar := argument!

lastChar

	^lastChar!

lastChar: argument 

	lastChar := argument! !

!CharRangeNode methodsFor: 'building parse trees'!

addChildrenInitial: anOrderedCollection 

	anOrderedCollection size = 2
		ifTrue: 
			[self firstChar: anOrderedCollection removeFirst.
			self lastChar: anOrderedCollection removeFirst]
		ifFalse: [self error: 'wrong number of children']! !

!CharRangeNode methodsFor: 'printing'!

printOn: aStream 

	self firstChar printOn: aStream.
	aStream nextPut: $-.
	self lastChar printOn: aStream! !

!CharRangeNode methodsFor: 'private'!

makeCharNodeFor: aChar 
	"Answer a new CharacterNode for aChar."

	^self characterNodeClass charSpec: (String with: aChar)! !

!CharRangeNode methodsFor: 'converting'!

addCharsTo: aCollection 
	"Add each character in my range to aCollection."

	self firstChar asInteger to: self lastChar asInteger do: [:ascii | aCollection add: (Character value: ascii)]!

addPureCharNodesTo: childNodes 
	"Add CharacterNodes for each character in my range to childNodes."

⌨️ 快捷键说明

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