[ENH] Lispy list functions

Bert Freudenberg bert at isgnw.CS.Uni-Magdeburg.De
Wed Sep 8 16:22:10 UTC 1999


Hi,

every Squeaker is a little bit of a Lisper, too, right? But even if not,
these functions come handy if you need a short stack or queue but don't
want to check for emptyness every time. So the one thing is simplicity. 
You just get it and if it's nil you're done. The other thing is memory
efficiency. It really bothers me if I have to use a Collection that will
have 0 or 1 elements in most cases (like a look-ahead buffer). Or look at
the implementation of dependents in Model: there is the hard-coded special
case of no dependents, answering #() if it's nil. Now here it comes:

"Change Set:		lispy-bf
Date:			3 September 1999
Author:			Bert Freudenberg

Adds some lispy methods: a list is nil (0 items) or an Object (1 item) or
an Array (2 or more items). Methods are #listHead, #listTail,
#listHeadAndTailIn:, and listDo: for accessing and #listHead: or
#listAppend: for construction.
This is handy and memory-efficient for those collections that usually have
zero or one elements."

And here are some examples for playing:

list := #(1 2).			"(1 2)"	"(setq list '(1 2))"
list listHead.			"1"	"(car list)"
list listTail.			"2"	"(cdr list)"
				"In Lisp this would be (2)!"
"Now list construction"
list := nil.
list listHead.			"nil"
list listTail.			"nil"
list := list listHead: 1.	"1"	"(setq list (cons 1 list))"
list listHead.			"1"
list listTail.			"nil"
list := list listHead: 2. 	"(2 1)"	"(setq list (cons 2 list))"
list listHead.			"2"
list listTail.			"1"
list := list listHead: 3.	"(3 2 1)"	"(setq list (cons 3 list))"
list listHead.			"3"
list listTail.			"(2 1)"
"listDo: is Smalltalk-like"
c := OrderedCollection new. list listDo: [:a | c add: a]. c.  "(3 2 1)"
"But this is lispier"
(1 to: 5) collect: [:i | list listHeadAndTailIn: [:h :t | list := t. h]]
				"(3 2 1 nil nil )"


Content-Type: TEXT/PLAIN; charset=US-ASCII; name="lispy-bf.8Sept520pm.cs"
Content-ID: <Pine.LNX.3.96.990908182210.19041H at balloon.cs.uni-magdeburg.de>
Content-Description: 

'From Squeak 2.5 of August 6, 1999 on 8 September 1999 at 5:20:56 pm'!
"Change Set:		lispy-bf
Date:			3 September 1999
Author:			Bert Freudenberg

Adds some lispy methods: a list is nil (0 items) or an Object (1 item) or an Array (2 or more items). Methods are #listHead, #listTail, #listHeadAndTailIn:, and listDo: for accessing and #listHead: or #listAppend: for construction.
This is handy and memory-efficient for those collections that usually have zero or one elements."!


!Object methodsFor: 'accessing' stamp: 'bf 9/3/1999 16:05'!
listAppend: anObject
	"Treat receiver as a list, append anObject"
	^Array with: self with: anObject! !

!Object methodsFor: 'accessing' stamp: 'bf 9/8/1999 15:57'!
listDo: aBlock
	"Treat receiver as a list"
	aBlock value: self! !

!Object methodsFor: 'accessing' stamp: 'bf 9/3/1999 13:56'!
listHead
	"Treat receiver as a list"
	^self! !

!Object methodsFor: 'accessing' stamp: 'bf 9/3/1999 16:04'!
listHead: anObject
	"Treat receiver as a list. Append anObject in front."
	^Array with: anObject with: self! !

!Object methodsFor: 'accessing' stamp: 'bf 9/3/1999 13:49'!
listHeadAndTailIn: aBlock
	"Treat receiver as a list. Evaluate aBlock with head and tail"
	^aBlock value: self value: nil! !

!Object methodsFor: 'accessing' stamp: 'bf 9/3/1999 13:56'!
listTail
	"Treat receiver as a list"
	^nil! !


!Array methodsFor: 'list accessing' stamp: 'bf 9/3/1999 16:05'!
listAppend: anObject
	"Treat receiver as a list, append anObject"
	^self copyWith: anObject! !

!Array methodsFor: 'list accessing' stamp: 'bf 9/8/1999 15:58'!
listDo: aBlock
	"Treat receiver as a list"
	self do: aBlock! !

!Array methodsFor: 'list accessing' stamp: 'bf 9/8/1999 16:21'!
listHead
	"Treat receiver as a list.  We always have at least 2 elements - but just in case"
	self size > 0 ifTrue: [^self first].
	^nil! !

!Array methodsFor: 'list accessing' stamp: 'bf 9/3/1999 16:04'!
listHead: anObject
	"Treat receiver as a list. Append anObject in front."
	| newColl newSize |
	newSize _ self size + 1.
	newColl_ self species new: newSize.
	newColl
		replaceFrom: 2
		to: newSize
		with: self
		startingAt: 1.
	newColl at: 1 put: anObject.
	^newColl! !

!Array methodsFor: 'list accessing' stamp: 'bf 9/3/1999 13:56'!
listHeadAndTailIn: aBlock
	"Treat receiver as a list. Evaluate aBlock with head and tail"
	^aBlock value: self listHead value: self listTail! !

!Array methodsFor: 'list accessing' stamp: 'bf 9/8/1999 16:23'!
listTail
	"Treat receiver as a list.  We always have at least 2 elements - but just in case"
	| sz |
	(sz _ self size) > 2 ifTrue: [^self allButFirst].
	sz == 2 ifTrue: [^self last].
	^nil! !


!UndefinedObject methodsFor: 'list accessing' stamp: 'bf 9/3/1999 14:51'!
listAppend: anObject
	"Treat receiver as a list, append anObject"
	^anObject! !

!UndefinedObject methodsFor: 'list accessing' stamp: 'bf 9/8/1999 15:57'!
listDo: aBlock
	"Treat receiver as a list"
	^self! !

!UndefinedObject methodsFor: 'list accessing' stamp: 'bf 9/3/1999 16:04'!
listHead: anObject
	"Treat receiver as a list. Append anObject in front."
	^anObject! !





More information about the Squeak-dev mailing list