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

📄 t-genmisc.st

📁 編譯器的語法產生器
💻 ST
📖 第 1 页 / 共 2 页
字号:
isTokenClassTerminal

	^'<*>' match: self! !

!String methodsFor: 'reconstructing'!

reconstructOn: aStream 

	self printOn: aStream! !

!Symbol methodsFor: 'testing'!

isNonterminal

	^true!

isTerminal

	^false!

isTokenClassTerminal

	^false! !

!SequenceableCollection methodsFor: 'enumerating'!

reverseDetect: aBlock ifNone: exceptionBlock 
	"Evaluate aBlock with each of the receiver's elements as the argument.
	Answer the last element for which aBlock evaluates to true."

	self reverseDo: [:each | (aBlock value: each) ifTrue: [^each]].
	^exceptionBlock value! !

!Set methodsFor: 'accessing'!

first
	"Answer an arbitrary element. If the receiver is empty, provide an error 
	notification. The selector 'first' is used for compatibility with 
	SequenceableCollections."

	self emptyCheck.
	self do: [:each | ^each]! !

!Set methodsFor: 'removing'!

removeFirst
	"Answer (and remove) an arbitrary element. The selector 'removeFirst' is used for 
	compatibility with SequenceableCollections."

	| element |
	element := self first.
	self remove: element.
	^element! !

!Set methodsFor: 'set operations'!

intersect: aSet 
	"Answer a new set which is the intersection of myself and aSet."

	^self size < aSet size
		ifTrue: [self select: [:each | aSet includes: each]]
		ifFalse: [aSet select: [:each | self includes: each]]!

union: aSet 
	"Answer a new set which is the union of myself and aSet."

	| newSet |
	newSet := self species new.
	newSet addAll: self; addAll: aSet.
	^newSet! !

!Dictionary methodsFor: 'accessing'!

elements

	^self values!

valuesAsSet
	"Answer a set containing the receiver's values."

	| aSet |
	aSet := Set new: self size.
	self do: [:each | aSet add: each].
	^aSet! !

!Dictionary methodsFor: 'converting'!

asDictionary

	^self! !

!Dictionary methodsFor: 'reconstructing'!

reconstructOn: aStream 
	"Emit #( keys ) and #( values ) on aSteam"

	aStream
		 poundSign;
		 leftParenthesis;
		 space.
	self
		associationsDo: 
			[:assoc | 
			assoc key reconstructOn: aStream.
			aStream space].
	aStream
		 rightParenthesis;
		 space;
		 poundSign;
		 leftParenthesis.
	self
		associationsDo: 
			[:assoc | 
			assoc value reconstructOn: aStream.
			aStream space].
	aStream rightParenthesis; space! !

Dictionary variableSubclass: #SetDictionary
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Collections-Unordered'!

SetDictionary comment:
'=================================================
    Copyright (c) 1992 by Justin O. Graver.
    All rights reserved (with exceptions).
    For complete information evaluate "Object tgenCopyright."
=================================================

This class represents a Dictionary of Sets.'!

!SetDictionary methodsFor: 'removing'!

at: key remove: anObject 

	^(self at: key)
		remove: anObject!

at: key remove: anObject ifAbsent: aBlock 

	^(self at: key)
		remove: anObject ifAbsent: aBlock! !

!SetDictionary methodsFor: 'accessing'!

at: key ifAbsent: absentBlock ifNotUnique: notUniqueBlock 

	| elementSet |
	elementSet := self at: key ifAbsent: [^absentBlock value].
	^elementSet size > 1
		ifTrue: [notUniqueBlock value]
		ifFalse: [elementSet first]!

at: key ifNotUnique: aBlock 

	| elementSet |
	elementSet := self at: key.
	^elementSet size > 1
		ifTrue: [aBlock value]
		ifFalse: [elementSet first]!

elements

	| elements |
	elements := Set new.
	self do: [:set | elements addAll: set].
	^elements! !

!SetDictionary methodsFor: 'adding'!

at: key add: anObject 

	(self at: key ifAbsent: [self at: key put: Set new])
		add: anObject!

at: key addAll: aSet 

	(self at: key ifAbsent: [self at: key put: Set new])
		addAll: aSet! !

!SetDictionary methodsFor: 'testing'!

isDeterministic

	self associationsDo: [:assoc | assoc value size > 1 ifTrue: [^false]].
	^true! !

!SetDictionary methodsFor: 'converting'!

asDictionary

	| newDict |
	self isDeterministic
		ifTrue: 
			[newDict := Dictionary new: self size.
			self associationsDo: [:assoc | newDict at: assoc key put: assoc value first].
			^newDict]
		ifFalse: [self error: 'SetDictionary cannot be converted to a Dictionary']! !

!SetDictionary methodsFor: 'dictionary enumerating'!

elementsDo: aBlock 
	"Evaluate aBlock with each element of each of the receiver's set elements as the 
	argument."

	self elements do: [:element | aBlock value: element]! !

Object subclass: #OrderedPair
	instanceVariableNames: 'x y'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Kernel-Objects'!

OrderedPair comment:
'=================================================
    Copyright (c) 1992 by Justin O. Graver.
    All rights reserved (with exceptions).
    For complete information evaluate "Object tgenCopyright."
=================================================

An OrderedPair extends the concept of a Point from Numbers to Objects. It is often
convenient to associate two objects together or to return a pair of objects from a
method.  OrderedPair provides the mechanism to do this without the inconvenience
of verbose syntax (as would be required if an Array or OrderedCollection were used).
The main instance creation method for OrderedPairs is the binary operator @.  This
operator is defined in Object and (now) overridden in Number so that numerical
points are treated and created in the traditional manner.

instance variables:
	x	<Object>	the first component of the pair
	y	<Object>	the second component of the pair
'!

!OrderedPair methodsFor: 'initialization'!

x: anObject y: anotherObject
	"initializes an OrderedPair"

	x := anObject.
	y := anotherObject.! !

!OrderedPair methodsFor: 'accessing'!

x
	"answer the first element of the pair"

	^x!

y
	"answer the second element of the pair"

	^y! !

!OrderedPair methodsFor: 'comparing'!

= anOrderedPair
	"answers whether two OrderedPairs are equal"

	^self species = anOrderedPair species
		and: [(x = anOrderedPair x) & (y = anOrderedPair y)]!

hash
	"answer the receiver's hash value"

	^(x hash bitShift: -1) + (y hash bitShift: -2)! !

!OrderedPair methodsFor: 'printing'!

printOn: aStream 
	"Append to the argument aStream a sequence of characters that identifies the receiver."

	x printOn: aStream.
	aStream nextPutAll: ' @ '.
	y printString printOn: aStream.! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

OrderedPair class
	instanceVariableNames: ''!

!OrderedPair class methodsFor: 'instance creation'!

x: anObject y: anotherObject
	"Answer a new OrderedPair whose x element is anObject and whose y element is anotherObject."

	^self new x: anObject y: anotherObject! !

!Object methodsFor: 'converting'!

@ anObject
	"Answer an OrderedPair with the receiver as the x element and anObject as the y element."

	^OrderedPair x: self y: anObject!

reversePairWith: x
	"Answer a new OrderedPair whose x value is the argument and whose y value is the receiver."

	^OrderedPair x: x y: self! !

!Number methodsFor: 'converting'!

@ y 
	"Answer a new pair (Point or OrderedPair or ...) whose x value is the receiver
	and whose y value is the argument.  Optional.  No Lookup.  See Object 
	documentation whatIsAPrimitive."

	<primitive: 18>
	^y reversePairWith: self!

reversePairWith: x
	"Answer a new Point whose x value is the argument and whose y value is the receiver."

	^Point x: x y: self! !

⌨️ 快捷键说明

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