How about Smalltalk-2000?

Hans-Martin Mosner hm.mosner at cityweb.de
Thu Feb 17 19:19:45 UTC 2000


Warren Postma wrote:

> >How much further do you want?  I'm serious - please explain, and you may
> >find (as here) that what you want already exists.
>
> Well, what about these array operations:
>
> a[5] := 10                                      " obvious array syntax "
> a[5][9] := 0                          " multiple levels of arrays "
> a[0:10] := 0                            " initialize a slice "
> a[5:10] := b[10:15]                     " slice "
> a["key"] := Value                       " dictionary "
>
> Warren

Although I really don't need a different Smalltalk syntax, this is a nice
homework example on how you can make the system suit your needs. Appended
you'll find the modifications needed to make Smalltalk do exactly what you
want to do, using exactly your syntax (actually, the key in your last
example is a comment in Smalltalk, you probably meant 'key').

Hans-Martin
-------------- next part --------------
'From Squeak2.7 of 5 January 2000 [latest update: #1762] on 17 February 2000 at 10:14:41 am'!
MessageNode subclass: #IndexedAccessNode
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'System-Compiler'!

!IndexedAccessNode commentStamp: 'hmm 2/17/2000 09:28' prior: 0!
Instances of this class represent at: and at:put: messages that were expressed using bracketed indexes, like these:
a[i]
a[i] _ x!

!IndexedAccessNode methodsFor: 'printing' stamp: 'hmm 2/17/2000 10:13'!
printOn: aStream indent: level

	receiver printOn: aStream indent: level precedence: 1.
	aStream nextPut: $[.
	arguments first printOn: aStream indent: level precedence: 1.
	(#(#at: #at:put:) includes: selector key) ifFalse: [
		"slice access"
		aStream nextPut: $:.
		arguments second printOn: aStream indent: level precedence: 1].
	aStream nextPut: $].
	(#(#at: #copyFrom:to:) includes: selector key) ifFalse: [
		"assignment or slice assignment"
		aStream nextPutAll: ' _ '.
		arguments last printOn: aStream indent: level+1 precedence: 1]! !


!Parser methodsFor: 'expression types' stamp: 'hmm 2/17/2000 09:08'!
expression

	(hereType == #word and: [tokenType == #leftArrow])
		ifTrue: [^ self assignment: self variable].
	self primaryExpression ifFalse: [^ false].
	[hereType == #leftBracket]
		whileTrue: [self indexedAccess].
	(self messagePart: 3 repeat: true)
		ifTrue: [hereType == #semicolon ifTrue: [self cascade]].
	^ true! !

!Parser methodsFor: 'expression types' stamp: 'hmm 2/17/2000 10:13'!
indexedAccess
	" [ index ] => IndexedAccessNode."

	| start receiver selector args |
	start _ self startOfNextToken.
	receiver _ parseNode.
	selector _ #at:.
	args _ OrderedCollection new.
	self match: #leftBracket.
	self expression ifFalse: [^self expected: 'expression'].
	args add: parseNode.
	(self match: #colon)
		ifTrue: [
			self expression ifFalse: [^self expected: 'expression'].
			selector _ #copyFrom:to:.
			args add: parseNode].
	(self match: #rightBracket)
		ifFalse: [^self expected: 'right bracket'].
	(self match: #leftArrow)
		ifTrue: [
			self expression ifFalse: [^self expected: 'expression'].
			selector _ selector = #at:
					ifTrue: [#at:put:]
					ifFalse: [#specialReplaceFrom:to:with:].
			args add: parseNode].
	parseNode _ IndexedAccessNode new
				receiver: receiver
				selector: selector
				arguments: args
				precedence: 1
				from: encoder
				sourceRange: (start to: self endOfLastToken).
	^true! !


!SequenceableCollection methodsFor: 'accessing' stamp: 'hmm 2/17/2000 10:05'!
specialReplaceFrom: start to: stop with: elementOrCollection
	"Utility method for slice assignment."
	((elementOrCollection isCollection) and: [elementOrCollection size = (stop-start+1)])
		ifTrue: [self replaceFrom: start to: stop with: elementOrCollection]
		ifFalse: [start to: stop do: [:i | self at: i put: elementOrCollection]].
	^elementOrCollection! !




More information about the Squeak-dev mailing list