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

📄 t-gen-tokenspecificationnodes.st

📁 編譯器的語法產生器
💻 ST
字号:
Object subclass: #TokenSpecificationRule
	instanceVariableNames: 'tokenClass regExpr directive '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'T-gen-Token Specification Nodes'!
TokenSpecificationRule comment:
'=================================================
    Copyright (c) 1992 by Justin O. Graver.
    All rights reserved (with exceptions).
    For complete information evaluate "Object tgenCopyright."
=================================================

Instance Variables:
	tokenClass	<String> - the name of the token class.
	regExpr		<RegularExpressionNode> (actually, any one of its concrete subclasses) - the (pure) regular expression tree representing the specification of the token class.
	directive 		<String + UndefinedObject> - the optional scanner directive.'!


!TokenSpecificationRule methodsFor: 'state accessing'!

directive

	^directive!

directive: argument 

	directive := argument!

regExpr

	^regExpr!

regExpr: argument 

	regExpr := argument!

tokenClass

	^tokenClass!

tokenClass: argument 

	tokenClass := argument! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

TokenSpecificationRule class
	instanceVariableNames: ''!


!TokenSpecificationRule class methodsFor: 'instance creation'!

tokenClass: arg1 regExpr: arg2 directive: arg3 

	| newMe |
	newMe := self new.
	newMe tokenClass: arg1.
	newMe regExpr: arg2.
	newMe directive: arg3.
	^newMe! !

ParseTreeNode subclass: #TokenSpecParseNode
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'T-gen-Token Specification Nodes'!
TokenSpecParseNode 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 token specification parse tree nodes.'!


TokenSpecParseNode subclass: #TokenSpecRuleNode
	instanceVariableNames: 'tokenClass regExpr directive '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'T-gen-Token Specification Nodes'!
TokenSpecRuleNode comment:
'=================================================
    Copyright (c) 1992 by Justin O. Graver.
    All rights reserved (with exceptions).
    For complete information evaluate "Object tgenCopyright."
=================================================


Instance Variables:
	tokenClass	<TokenClassNode> - the name of the token class.
	regExpr		<RegularExpressionNode> (actually, any one of its concrete subclasses) - the regular expression tree representing the specification of the token class.
	directive 		<DirectiveNode + UndefinedObject> - the optional scanner directive.'!


!TokenSpecRuleNode methodsFor: 'state accessing'!

directive

	^directive!

directive: argument 

	directive := argument!

regExpr

	^regExpr!

regExpr: argument 

	regExpr := argument!

tokenClass

	^tokenClass!

tokenClass: argument 

	tokenClass := argument! !

!TokenSpecRuleNode methodsFor: 'building parse trees'!

addChildrenInitial: anOrderedCollection 

	anOrderedCollection size = 3
		ifTrue: 
			[self tokenClass: anOrderedCollection removeFirst.
			self regExpr: anOrderedCollection removeFirst.
			self directive: anOrderedCollection removeFirst]
		ifFalse: [self error: 'wrong number of children']! !

!TokenSpecRuleNode methodsFor: 'printing'!

printOn: aStream 

	self tokenClass printOn: aStream.
	aStream tab; nextPutAll: ': '.
	self regExpr printOn: aStream.
	aStream tab; tab.
	self directive notNil 
		ifTrue:
			[self directive printOn: aStream.
			aStream space].
	aStream nextPut: $;! !

!TokenSpecRuleNode methodsFor: 'private'!

specRuleClass

	^TokenSpecificationRule! !

!TokenSpecRuleNode methodsFor: 'converting'!

asSpecRule
	"Answer the specification rule I represent."

	^self specRuleClass
		tokenClass: self tokenClass symbol
		regExpr: self regExpr asPureRegExpr
		directive: (self directive notNil
				ifTrue: [self directive asMessageSelector]
				ifFalse: [nil])! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

TokenSpecRuleNode class
	instanceVariableNames: ''!


!TokenSpecRuleNode class methodsFor: 'instance creation'!

tokenClass: arg1 regExpr: arg2 directive: arg3 

	| newMe |
	newMe := self new.
	newMe tokenClass: arg1.
	newMe regExpr: arg2.
	newMe directive: arg3.
	^newMe! !

TokenSpecParseNode subclass: #TokenSpecNode
	instanceVariableNames: 'specRules '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'T-gen-Token Specification Nodes'!
TokenSpecNode 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 token specification.

Instance Variables:

	specRules	<OrderedCollection>	- the rules for this spec.'!


!TokenSpecNode methodsFor: 'state accessing'!

specRules

	^specRules!

specRules: argument 

	specRules := argument! !

!TokenSpecNode methodsFor: 'building parse trees'!

addChildrenFirst: anOrderedCollection 

	self specRules addAllFirst: anOrderedCollection!

addChildrenInitial: anOrderedCollection 

	self specRules addAll: anOrderedCollection! !

!TokenSpecNode methodsFor: 'initialization'!

init

	self specRules: OrderedCollection new! !

!TokenSpecNode methodsFor: 'printing'!

printOn: aStream 

	self specRules do: 
		[:rule | 
		rule printOn: aStream.
		aStream cr]! !

!TokenSpecNode methodsFor: 'converting'!

asSpecRuleList
	"Answer the collection of specification rules I represent."

	| rules |
	rules := OrderedCollection new.
	self specRules do: [:rule | rules add: rule asSpecRule].
	^rules! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

TokenSpecNode class
	instanceVariableNames: ''!


!TokenSpecNode class methodsFor: 'instance creation'!

new

	^super new init! !

TokenSpecParseNode subclass: #TokenSpecLeafNode
	instanceVariableNames: 'symbol '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'T-gen-Token Specification Nodes'!
TokenSpecLeafNode 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 token spec leaf nodes.

Instance Variables:

	symbol	<Character>	- token symbol'!


!TokenSpecLeafNode methodsFor: 'state accessing'!

symbol

	^symbol!

symbol: argument 

	symbol := argument! !

!TokenSpecLeafNode methodsFor: 'building parse trees'!

setAttribute: value 

	self symbol: value! !

!TokenSpecLeafNode methodsFor: 'printing'!

printOn: aStream 

	aStream nextPutAll: self symbol! !

TokenSpecLeafNode subclass: #DirectiveNode
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'T-gen-Token Specification Nodes'!
DirectiveNode comment:
'=================================================
    Copyright (c) 1992 by Justin O. Graver.
    All rights reserved (with exceptions).
    For complete information evaluate "Object tgenCopyright."
=================================================

I hold the token class directive.'!


!DirectiveNode methodsFor: 'converting'!

asMessageSelector
	"My symbol is a string of the form '{selector}'. 
	Trim the braces and answer the selector symbol."

	^(self symbol copyFrom: 2 to: self symbol size - 1) asSymbol! !

TokenSpecLeafNode subclass: #TokenClassNode
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'T-gen-Token Specification Nodes'!
TokenClassNode comment:
'=================================================
    Copyright (c) 1992 by Justin O. Graver.
    All rights reserved (with exceptions).
    For complete information evaluate "Object tgenCopyright."
=================================================

I hold the token class.'!


⌨️ 快捷键说明

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