[squeak-dev] Re: A criticism of the Nile paper (was Re: My view on Traits)

Andreas Raab andreas.raab at gmx.de
Sat May 17 20:32:54 UTC 2008


Damien Cassou wrote:
> I'm sorry. I haven't updated the universe package for some time.
> Please use SqueakSource and load Nile-All. This package depends on
> other required package and contains NSMetrics.

Okay, after loading this I understand better where the numbers come 
from. First, a couple of comments on NSMetrics: 
#methodsInClassAndMetaclass:methodListBlock: does a union of methods in 
class and metaclass which looks a little questionable to me. I don't 
think it matters here but it seems odd to count a method in class and 
metaclass only once. The #numberOfReimplementedMethodsForClasses: also 
has two problems in such that it does only look at methods overridden in 
the direct superclass (so it doesn't find methods implemented in Stream 
and overridden in ReadStream but not in PositionableStream) and that it 
excludes the required selectors of traits but not those of superclasses 
(i.e., self subclassResponsibility) which it should discount as well 
(see note below on the metrics that are affected by it).

That said, we can now devise a comparison which is more appropriate for 
a Nile vs. Squeak comparison. I've attached a simple class 
InternalStream which as a subclass of PositionableStream implements the 
same folding of ReadStream, WriteStream, and ReadWriteStream. I believe 
it to be a fully functioning equivalent to NSCollectionStream. If we run 
the design metrics using InternalStream instead of the three other 
classes we end up with metrics that look like this (slightly reformatted 
from the TeX output):

                                  Squeak  Nile (Squeak-Nile)/Squeak
Number of Classes And Traits        3      6          -100%
Number of Classes                   3      1            66%
Number of Methods                  39     33            15% [*1]
Number of Bytes                  1328   1078            18%
Number of Cancelled Methods         0      0             0%
Number of Reimplemented Methods    10      3            70% [*1]
Number of Methods Impl. Too High    0      0             0%

[*1] This includes 2 subclassResponsibilities in Squeak which should be 
discounted as pointed out above.

The main differences are in the number of entities as well as in the 
number of methods (overrides). Looking at it in detail it turns out that 
the larger number of entities comes purely from the more fine-grained 
structure of traits (only one class but five traits) and the larger 
number of methods come from overrides where InternalStream has either 
more efficient versions (#upTo: #next: #upToEnd) or needs to compensate 
PositionableStream assuming that the position will be within its 
readLimit (#position: #setToEnd #reset) or implements required 
subclassResponsibilities (#atEnd, #contents).

It is interesting to see that the traits version can do without most of 
those overrides although it isn't clear to me that this would remain a 
lasting advantage. One could rewrite the Squeak collection hierarchy to 
do without these overrides by relaxing the constraints on 
PositionableStream and use more effective versions by default. This 
would improve these metrics but I'm not sure it is in the spirit of the 
Squeak collection hierarchy.

That said, I would also slightly refactor NSCollectionStream into, e.g.,

NSPositionableStream <NSTGettableStream + NSPuttableStream + 
NSPositionableStream>
   NSCollectionStream

The idea in the above refactoring is to keep the "composition class" 
(NSPositionableStream) separate from the "implementation class" 
(NSCollectionStream). It really makes it easier to see what you've done 
in NSCollectionStream and having a class used only to gather the traits 
also makes it more clear that anything you'd implement at that level 
really belongs into a trait and not into the class. It makes looking at 
classes with traits almost bearable ;-)

Cheers,
   - Andreas
-------------- next part --------------
'From Squeak3.9.1 of 2 March 2008 [latest update: #7075] on 17 May 2008 at 1:19:35 pm'!
PositionableStream subclass: #InternalStream
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Collections-Streams'!
!InternalStream commentStamp: 'ar 5/17/2008 07:44' prior: 0!
Simple class combining ReadStream, WriteStream and ReadWriteStream.!


!InternalStream methodsFor: 'initialize' stamp: 'ar 5/17/2008 08:46'!
on: aCollection from: firstIndex to: lastIndex

	| len |
	collection := aCollection.
	readLimit := lastIndex > (len := collection size)
						ifTrue: [len]
						ifFalse: [lastIndex].
	position := firstIndex <= 1
				ifTrue: [0]
				ifFalse: [firstIndex - 1]! !


!InternalStream methodsFor: 'accessing' stamp: 'ar 5/17/2008 07:32'!
ascii! !

!InternalStream methodsFor: 'accessing' stamp: 'ar 5/17/2008 07:32'!
readStream
	"polymorphic with SequenceableCollection.  Return self"
	^ self! !

!InternalStream methodsFor: 'accessing' stamp: 'ar 5/17/2008 07:39'!
size
	"Compatibility with other streams (e.g., FileStream)"
	^readLimit := readLimit max: position! !

!InternalStream methodsFor: 'accessing' stamp: 'ar 5/17/2008 08:45'!
writeLimit
	^collection size! !


!InternalStream methodsFor: 'reading' stamp: 'ar 5/17/2008 07:31'!
next
	"Primitive. Answer the next object in the Stream represented by the
	receiver. Fail if the collection of this stream is not an Array or a String.
	Fail if the stream is positioned at its end, or if the position is out of
	bounds in the collection. Optional. See Object documentation
	whatIsAPrimitive."

	<primitive: 65>
	position >= readLimit
		ifTrue: [^nil]
		ifFalse: [^collection at: (position _ position + 1)]! !

!InternalStream methodsFor: 'reading' stamp: 'ar 5/17/2008 07:34'!
next: anInteger 
	"Answer the next anInteger elements of my collection.  overriden for efficiency"
	| ans endPosition |
	readLimit := readLimit max: position.
	endPosition := position + anInteger  min:  readLimit.
	ans := collection copyFrom: position+1 to: endPosition.
	position := endPosition.
	^ans
! !

!InternalStream methodsFor: 'reading' stamp: 'ar 5/17/2008 07:32'!
next: n into: aCollection startingAt: startIndex
	"Read n objects into the given collection. 
	Return aCollection or a partial copy if less than
	n elements have been read."
	| max |
	max := (readLimit - position) min: n.
	aCollection 
		replaceFrom: startIndex 
		to: startIndex+max-1
		with: collection
		startingAt: position+1.
	position := position + max.
	max = n
		ifTrue:[^aCollection]
		ifFalse:[^aCollection copyFrom: 1 to: startIndex+max-1]! !

!InternalStream methodsFor: 'reading' stamp: 'ar 5/17/2008 07:32'!
upTo: anObject
	"fast version using indexOf:"
	| start end |

	start := position+1.
	end := collection indexOf: anObject startingAt: start ifAbsent: [ 0 ].

	"not present--return rest of the collection"	
	end = 0 ifTrue: [ ^self upToEnd ].

	"skip to the end and return the data passed over"
	position := end.
	^collection copyFrom: start to: (end-1)! !

!InternalStream methodsFor: 'reading' stamp: 'ar 5/17/2008 07:33'!
upToEnd
	| start |
	start := position+1.
	position := collection size.
	^collection copyFrom: start to: position! !


!InternalStream methodsFor: 'writing' stamp: 'ar 5/17/2008 08:50'!
next: anInteger putAll: aCollection startingAt: startIndex
	"Store the next anInteger elements from the given collection."
	| newEnd numPut |
	collection class == aCollection class ifFalse:
		[^ super next: anInteger putAll: aCollection startingAt: startIndex ].

	numPut := anInteger min: (aCollection size - startIndex + 1).
	newEnd := position + numPut.
	newEnd > self writeLimit ifTrue:
		[^ super next: anInteger putAll: aCollection startingAt: startIndex "Trigger normal pastEndPut: logic"].

	collection replaceFrom: position+1 to: newEnd with: aCollection startingAt: startIndex.
	position := newEnd.
! !

!InternalStream methodsFor: 'writing' stamp: 'ar 5/17/2008 08:46'!
nextPut: anObject 
	"Primitive. Insert the argument at the next position in the Stream
	represented by the receiver. Fail if the collection of this stream is not an
	Array or a String. Fail if the stream is positioned at its end, or if the
	position is out of bounds in the collection. Fail if the argument is not
	of the right type for the collection. Optional. See Object documentation
	whatIsAPrimitive."

	<primitive: 66>
	((collection class == ByteString) and: [
		anObject isCharacter and:[anObject isOctetCharacter not]]) ifTrue: [
			collection _ (WideString from: collection).
			^self nextPut: anObject.
	].
	position >= self writeLimit
		ifTrue: [^ self pastEndPut: anObject]
		ifFalse: 
			[position _ position + 1.
			^collection at: position put: anObject]! !

!InternalStream methodsFor: 'writing' stamp: 'ar 5/17/2008 08:46'!
nextPutAll: aCollection

	| newEnd |
	collection class == aCollection class ifFalse:
		[^ super nextPutAll: aCollection ].

	newEnd := position + aCollection size.
	newEnd > self writeLimit ifTrue:
		[self growTo: newEnd + 10].

	collection replaceFrom: position+1 to: newEnd  with: aCollection startingAt: 1.
	position := newEnd.! !


!InternalStream methodsFor: 'positioning' stamp: 'ar 5/17/2008 07:40'!
position: anInteger 
	"Refer to the comment in PositionableStream|position:."
	readLimit := readLimit max: position.
	super position: anInteger! !

!InternalStream methodsFor: 'positioning' stamp: 'ar 5/17/2008 07:40'!
reset 
	"Refer to the comment in PositionableStream|reset."
	readLimit := readLimit max: position.
	position := 0.! !

!InternalStream methodsFor: 'positioning' stamp: 'ar 5/17/2008 07:41'!
resetToStart
	readLimit := position := 0.! !

!InternalStream methodsFor: 'positioning' stamp: 'ar 5/17/2008 07:41'!
setToEnd 
	"Refer to the comment in PositionableStream|setToEnd."

	readLimit := readLimit max: position.
	super setToEnd.! !


!InternalStream methodsFor: 'private' stamp: 'ar 5/17/2008 08:45'!
growTo: anInteger

   " anInteger is the required minimal new size of the collection "
	| oldSize grownCollection newSize |
	oldSize := collection size.
     newSize := anInteger + (oldSize // 4 max: 20).
	grownCollection := collection class new: newSize.
	collection := grownCollection replaceFrom: 1 to: oldSize with: collection startingAt: 1.
! !

!InternalStream methodsFor: 'private' stamp: 'ar 5/17/2008 08:50'!
pastEndPut: anObject
	"Grow the collection by creating a new bigger collection and then
	copy over the contents from the old one. We grow by doubling the size
	but the growth is kept between 20 and 1000000.
	Finally we put <anObject> at the current write position."

	| oldSize grownCollection |
	oldSize := collection size.
	grownCollection := collection class new: oldSize + ((oldSize max: 20) min: 1000000).
	collection := grownCollection replaceFrom: 1 to: oldSize with: collection startingAt: 1.
	collection at: (position := position + 1) put: anObject.
	"return the argument - added by kwl"
	^ anObject! !

!InternalStream methodsFor: 'private' stamp: 'ar 5/17/2008 08:46'!
with: aCollection

	super on: aCollection.
	position := readLimit := aCollection size! !

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

InternalStream class
	instanceVariableNames: ''!

!InternalStream class methodsFor: 'instance creation' stamp: 'ar 5/17/2008 07:44'!
on: aCollection from: firstIndex to: lastIndex 
	"Answer an instance of me on a copy of the argument, aCollection, 
	determined by the indices firstIndex and lastIndex. Position the instance 
	at the beginning of the collection."

	^self basicNew
		on: aCollection
		from: firstIndex
		to: lastIndex! !

!InternalStream class methodsFor: 'instance creation' stamp: 'ar 5/17/2008 07:44'!
with: aCollection 
	"Answer an instance of me on the argument, aCollection, positioned to 
	store objects at the end of aCollection."

	^self basicNew with: aCollection! !

!InternalStream class methodsFor: 'instance creation' stamp: 'ar 5/17/2008 07:44'!
with: aCollection from: firstIndex to: lastIndex 
	"Answer an instance of me on the subcollection of the argument, 
	aCollection, determined by the indices firstIndex and lastIndex. Position 
	the instance to store at the end of the subcollection."

	^self basicNew with: (aCollection copyFrom: firstIndex to: lastIndex)! !


More information about the Squeak-dev mailing list