[ENH] UpArrow as operator (was: Must _ go like the Dodo?)

Bert Freudenberg bert at isgnw.CS.Uni-Magdeburg.De
Wed Mar 17 20:50:46 UTC 1999


Doug Way wrote:

> I guess a better argument for using something other than ^ for returning
> is that you could then use ^ in place of raisedTo:, e.g. x^2, which is
> semi-standard typed-math notation.  (When was this introduced?)  Still,
> it ain't gonna happen. :-)

What's not gonna happen? Using ^ as an operator is as easy as using |
(there is code in the parser to special-case the vertical bar). The
attached changeset patches the parser and adds Number>>#^ to give the
expected result ...

Enjoy :-)

/bert

-- 
 Bert Freudenberg                                            Department of
                                                            Simulation and
 mailto:bert at isg.cs.uni-magdeburg.de                     Computer Graphics
 http://isgwww.cs.uni-magdeburg.de/isg/bert.html        Univ. of Magdeburg

Content-Type: TEXT/PLAIN; charset=US-ASCII; name="upArrowOperator-bf.cs"
Content-ID: <Pine.LNX.3.96.990317215046.28254G at balloon.cs.uni-magdeburg.de>
Content-Description: 

'From Squeak 2.3 of January 14, 1999 on 17 March 1999 at 9:29:05 pm'!
"Change Set:		upArrowOperator-bf
Date:			17 March 1999
Author:			Bert Freudenberg

Makes the upArrow ^ usable as a binary selector. Provides Number>>#^ as equivalent to #raisedTo:"!


!Parser methodsFor: 'expression types' stamp: 'bf 3/17/1999 20:51'!
messagePart: level repeat: repeat

	| start receiver selector args precedence words keywordStart |
	[receiver _ parseNode.
	(hereType == #keyword and: [level >= 3])
		ifTrue: 
			[start _ self startOfNextToken.
			selector _ WriteStream on: (String new: 32).
			args _ OrderedCollection new.
			words _ OrderedCollection new.
			[hereType == #keyword]
				whileTrue: 
					[keywordStart _ self startOfNextToken + requestorOffset.
					selector nextPutAll: self advance.
					words addLast: (keywordStart to: self endOfLastToken + requestorOffset).
					self primaryExpression ifFalse: [^self expected: 'Argument'].
					self messagePart: 2 repeat: true.
					args addLast: parseNode].
			(Symbol hasInterned: selector contents ifTrue: [ :sym | selector _ sym])
				ifFalse: [ selector _ self correctSelector: selector contents
										wordIntervals: words
										exprInterval: (start to: self endOfLastToken)
										ifAbort: [ ^ self fail ] ].
			precedence _ 3]
		ifFalse: [((hereType == #binary or: [hereType == #verticalBar or: [hereType == #upArrow]])
				and: [level >= 2])
				ifTrue: 
					[start _ self startOfNextToken.
					selector _ self advance asSymbol.
					self primaryExpression ifFalse: [^self expected: 'Argument'].
					self messagePart: 1 repeat: true.
					args _ Array with: parseNode.
					precedence _ 2]
				ifFalse: [hereType == #word
						ifTrue: 
							[start _ self startOfNextToken.
							selector _ self advance.
							args _ #().
							words _ OrderedCollection with: (start  + requestorOffset to: self endOfLastToken + requestorOffset).
							(Symbol hasInterned: selector ifTrue: [ :sym | selector _ sym])
								ifFalse: [ selector _ self correctSelector: selector
													wordIntervals: words
													exprInterval: (start to: self endOfLastToken)
													ifAbort: [ ^ self fail ] ].
							precedence _ 1]
						ifFalse: [^args notNil]]].
	parseNode _ MessageNode new
				receiver: receiver
				selector: selector
				arguments: args
				precedence: precedence
				from: encoder
				sourceRange: (start to: self endOfLastToken).
	repeat]
		whileTrue: [].
	^true! !

!Parser methodsFor: 'expression types' stamp: 'bf 3/17/1999 20:52'!
pattern: fromDoit inContext: ctxt 
	" unarySelector | binarySelector arg | keyword arg {keyword arg} => 
	{selector, arguments, precedence}."

	| args selector |
	fromDoit 
		ifTrue: 
			[ctxt == nil
				ifTrue: [^Array with: #DoIt with: #() with: 1]
				ifFalse: [^Array 
							with: #DoItIn: 
							with: (Array 
									with: (encoder encodeVariable: 'homeContext')) 
									with: 3]].
	hereType == #word 
		ifTrue: [^Array with: self advance asSymbol with: #() with: 1].
	(hereType == #binary or: [hereType == #verticalBar or: [hereType == #upArrow]])
		ifTrue: 
			[selector _ self advance asSymbol.
			args _ Array with: (encoder bindArg: self argumentName).
			^Array with: selector with: args with: 2].
	hereType == #keyword
		ifTrue: 
			[selector _ WriteStream on: (String new: 32).
			args _ OrderedCollection new.
			[hereType == #keyword]
				whileTrue: 
					[selector nextPutAll: self advance.
					args addLast: (encoder bindArg: self argumentName)].
			^Array with: selector contents asSymbol with: args with: 3].
	^self expected: 'Message pattern'! !

!Number methodsFor: 'arithmetic' stamp: 'bf 3/17/1999 20:54'!
^ aNumber 
	"Answer the receiver raised to aNumber."

	^ self raisedTo: aNumber! !





More information about the Squeak-dev mailing list