One for the students: Literal arrays

Andreas Raab raab at isgnw.cs.Uni-Magdeburg.DE
Fri Jun 5 22:43:57 UTC 1998


Folks,

A couple of days ago students told me about a mysterious problem. It
turned out that they had modified a literal array without noticing.
Since I had the problem myself I know that it can give you a real
headache. Attached is the fix: class LiteralArray plus a one-word fix in
the Scanner ;-)

Students on the list (in particular those from Magdeburg ;-)), listen up!
If you didn't entirely understand the above, here is the comment from
class LiteralArray which should make the problem and the solution clearer:

A LiteralArray represents an array that is basically read-only. This is
because I represent a constant literal object which should not be modified
accidentally. Literal arrays are usually created by the compiler and
stored in CompiledMethods. Since these arrays are only created once (e.g.,
at compile time of the method), it is easy to store different values so
that on each method activation the actual contents of the array changes.
So, for instance, the method

doubleFirstArrayElement: anArray
	^anArray at: 1 put: (anArray at: 1) * 2 

will work perfectly unless you use it like

literalProblem
	^self doubleFirstArrayElement: #( 1 ).

The above Array will upon each activation of #literalProblem double the
value stored in it. Even worse, as long as your source code is intact, the
source will always show you the value stored during compilation. NOTE:
This is an *example* to show the basic problem. If you really run into it,
it will be *much* more complicated to find.

Bye,
  Andreas
--
Linear algebra is your friend - Trigonometry is your enemy.
+===== Andreas Raab ============= (raab at isg.cs.uni-magdeburg.de) =====+
I Department of Simulation and Graphics      Phone: +49 391 671 8065  I
I University of Magdeburg, Germany           Fax:   +49 391 671 1164  I
+=============< http://isgwww.cs.uni-magdeburg.de/~raab >=============+

Content-Type: TEXT/PLAIN; charset=US-ASCII; name="LiteralArray.cs"
Content-ID: <Pine.SGI.3.95.980606004357.22853B at monet>
Content-Description: 

'From Squeak 2.0 of May 22, 1998 on 6 June 1998 at 12:18:37 am'!
Array variableSubclass: #LiteralArray
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Collections-Arrayed'!

!Array methodsFor: 'converting' stamp: 'ar 6/5/1998 23:57'!
asDeepArray
	"Return a deep copy of the receiver containing no literal arrays"
	^self collect:[:element| 
		(element isKindOf: LiteralArray) 
			ifTrue:[element asDeepArray]
			ifFalse:[element]]! !

!Array methodsFor: 'converting' stamp: 'ar 6/5/1998 23:56'!
asDeepLiteralArray
	"Return a copy of the receiver containing only literal arrays"
	self doWithIndex:[:element :index| 
		(element isKindOf: Array) 
			ifTrue:[self at: index put: element asDeepLiteralArray]].
	^self asLiteralArray! !

!Array methodsFor: 'converting' stamp: 'ar 6/5/1998 23:57'!
asLiteralArray
	"Note: This method is optimized for speed."
	^(LiteralArray new: self size) replaceFrom: 1 to: self size with: self startingAt: 1! !


!LiteralArray commentStamp: 'ar 6/6/1998 00:18' prior: 0!
A LiteralArray represents an array that is basically read-only. This is because I represent a constant literal object which should not be modified accidentally. Literal arrays are usually created by the compiler and stored in CompiledMethods. Since these arrays are only created once (e.g., at compile time of the method), it is easy to store different values so that on each method activation the actual contents of the array changes. So, for instance, the method

doubleFirstArrayElement: anArray
	^anArray at: 1 put: (anArray at: 1) * 2 

will work perfectly unless you use it like

literalProblem
	^self doubleFirstArrayElement: #( 1 ).

The above Array will upon each activation of #literalProblem double the value stored in it. Even worse, as long as your source code is intact, the array will always show you the value stored during compilation. NOTE: This is an *example* to show the basic problem. If you really run into it, it will be *much* more complicated -- believe me, I had it and others too.!

!LiteralArray methodsFor: 'accessing' stamp: 'ar 6/5/1998 23:32'!
at: index put: value
	"Literal arrays should not be accessed by #at:put:"
	^self shouldNotImplement! !

!LiteralArray methodsFor: 'accessing' stamp: 'ar 6/5/1998 23:32'!
species
	^Array! !

!LiteralArray methodsFor: 'testing' stamp: 'ar 6/5/1998 23:35'!
isLiteral
	"I am supposed to be literal"
	^true! !

!LiteralArray methodsFor: 'converting' stamp: 'ar 6/5/1998 23:46'!
asArray
	"Optimized for speed but equivalent to
		^self collect:[:any| any]
	"
	^(Array new: self size) replaceFrom: 1 to: self size with: self startingAt: 1! !

!LiteralArray methodsFor: 'converting' stamp: 'ar 6/5/1998 23:58'!
asDeepLiteralArray
	"Overridden since we may contain any non-literal arrays"
	^self asArray asDeepLiteralArray! !

!LiteralArray methodsFor: 'converting' stamp: 'ar 6/5/1998 23:40'!
asLiteralArray
	^self! !

!LiteralArray methodsFor: 'printing' stamp: 'ar 6/5/1998 23:35'!
printOn: aStream
	^self storeOn: aStream! !


!LiteralArray class methodsFor: 'class initialization' stamp: 'ar 6/5/1998 23:53'!
initializeMethodLiterals
	"LiteralArray initializeMethodLiterals"
	| literal |
	CompiledMethod allInstancesDo:[:cm|
		1 to: cm numLiterals do:[:i|
			literal _ cm literalAt: i.
			literal class == Array 
				ifTrue:[cm literalAt: i put: literal asDeepLiteralArray]]].
! !

!LiteralArray class methodsFor: 'examples' stamp: 'ar 6/5/1998 23:41'!
badExample1
	"LiteralArray badExample1"
	#(1 2 3) at: 1 put: 2! !

!LiteralArray class methodsFor: 'examples' stamp: 'ar 6/5/1998 23:41'!
badExample2
	"LiteralArray badExample2"
	#(1 #(2 3)) last at: 1 put: 2! !

!LiteralArray class methodsFor: 'examples' stamp: 'ar 6/5/1998 23:43'!
goodExample1
	"LiteralArray goodExample1"
	#(1 2 3) asArray at: 1 put: 2! !

!LiteralArray class methodsFor: 'examples' stamp: 'ar 6/5/1998 23:49'!
goodExample2
	"LiteralArray goodExample2"
	#(1 #(2 3)) asDeepArray last at: 1 put: 2! !


!Scanner methodsFor: 'expression types' stamp: 'ar 6/5/1998 23:40'!
scanLitVec

	| s |
	s _ WriteStream on: (Array new: 16).
	[tokenType = #rightParenthesis or: [tokenType = #doIt]]
		whileFalse: 
			[tokenType = #leftParenthesis
				ifTrue: 
					[self scanToken; scanLitVec]
				ifFalse: 
					[tokenType = #word | (tokenType = #keyword)
						ifTrue: 
							[self scanLitWord]
						ifFalse:
							[(token == #- 
									and: [(typeTable at: hereChar asciiValue) = #xDigit])
								ifTrue: 
									[self scanToken.
									token _ token negated]]].
			s nextPut: token.
			self scanToken].
	token _ s contents asLiteralArray! !





More information about the Squeak-dev mailing list