LinkedList.st
author Claus Gittinger <cg@exept.de>
Thu, 23 Nov 1995 02:19:14 +0100
changeset 606 7a9ab63a6757
parent 530 07d0bce293c9
child 629 2ceefe9b5a19
permissions -rw-r--r--
checkin from browser

"
 COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

SequenceableCollection subclass:#LinkedList
	 instanceVariableNames:'firstLink lastLink numberOfNodes'
	 classVariableNames:''
	 poolDictionaries:''
	 category:'Collections-Sequenceable'
!

!LinkedList class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    this class implements an anchor to a list of Links.
    The data itself is held in the link elements. 
    See (the abstract) Link, ValueLink and (possibly other) classes,
    which can be used as elements of a linkedList.

    LinkedList does not care for storage; all it does is handling
    chained link elements, which must respond to #nextLink/#nextLink:.
    (i.e. any object which can do this, can be used as elements of a linked
    list).

    Although LinkedList is a subclass of SequenceableCollection (and therefore
    supports indexed access via at:), you should be careful in using it or
    other methods based upon at:. 
    The reason is that #at: walks the linkedlist to find the indexed element
    and is therefore slow. 
    This means that some linear-in-time algorithms inherited from 
    SequenceableCollection become square in runtime.
    In general, if you need access via a numeric index, you better use Array,
    OrderedCollection or similar.

    For the above reasons, the system does not make heavily use of LinkedLists;
    the only good application is where elements must be repeatedly be removed
    at the front and added at the end.
    (the schedulers process handling code does this to manage process lists.)
"
!

examples 
"
    |l|

    l := LinkedList new.
    l addLast:(ValueLink new value:'one').
    l addLast:(ValueLink new value:'two').
    l addLast:(ValueLink new value:'three').
    l addLast:(ValueLink new value:'four').
    l inspect


    |l|

    l := LinkedList new.
    l addLast:(ValueLink new value:'one').
    l addLast:(ValueLink new value:'two').
    l addLast:(ValueLink new value:'three').
    l addLast:(ValueLink new value:'four').
    (l at:3) value inspect.        'slow operation for large lists'.


    |l link|

    l := LinkedList new.
    l addLast:(ValueLink new value:'one').
    l addLast:(ValueLink new value:'two').
    l addLast:(ValueLink new value:'three').
    l addLast:(ValueLink new value:'four').
    link := l removeFirst.
    l addLast:link.
    l inspect.     
"
!

version
    ^ '$Header: /cvs/stx/stx/libbasic/LinkedList.st,v 1.20 1995-11-23 01:18:20 cg Exp $'
! !

!LinkedList class methodsFor:'instance creation'!

new
    "create and return a new LinkedList"

    ^ super new initialize
! !

!LinkedList methodsFor:'accessing'!

at:index
    "return the n'th element - use of this method should be avoided,
     since it is slow to walk through the list - think about using
     another collection if you need index access.
     Notice, that many methods in SeqColl are based on at:-access,
     so other inherited methods may be very slow (showing square runtime)."

    |theLink
     runIndex "{Class: SmallInteger}"|

    theLink := firstLink.
    runIndex := 1.
    [runIndex == index] whileFalse:[
	theLink isNil ifTrue:[^ self subscriptBoundsError:index].
	theLink := theLink nextLink.
	runIndex := runIndex + 1.
    ].
    ^ theLink
!

first
    "return the first node in the list"

    firstLink isNil ifTrue:[self emptyCollectionError].
    ^ firstLink
!

last
    "return last node in the list"

    lastLink isNil ifTrue:[self emptyCollectionError].
    ^ lastLink
! !

!LinkedList methodsFor:'adding & removing'!

add:aLink
    "adds aLink to the end of the sequence. Returns aLink"

    aLink nextLink:nil.
    lastLink isNil ifTrue:[
	firstLink := aLink
    ] ifFalse: [
	lastLink nextLink:aLink
    ].
    lastLink := aLink.
    numberOfNodes := numberOfNodes + 1.
    ^ aLink
!

add:linkToAdd after:aLink
    "adds linkToAdd after another link, aLink. If aLink is nil,
     linkToAdd is inserted at the beginning. Returns linkToAdd."

    |this|

    aLink isNil ifTrue:[^ self addFirst:linkToAdd ].

    this := firstLink.
    [this notNil and:[this ~~ aLink]] whileTrue:[
	this := this nextLink
    ].
    this isNil ifTrue:[^ self add:linkToAdd ].
    linkToAdd nextLink:(this nextLink).
    this nextLink:linkToAdd.
    ^ linkToAdd
!

addFirst:aLink
    "adds aLink to the beginning of the sequence. Returns aLink"

    firstLink isNil ifTrue:[
	firstLink := aLink.
	lastLink := aLink
    ] ifFalse: [
	aLink nextLink:firstLink.
	firstLink := aLink
    ].
    numberOfNodes := numberOfNodes + 1.
    ^ aLink
!

remove:aLink ifAbsent:exceptionBlock
    "remove the argument, aLink from the sequence; if absent,
     evaluate the exceptionBlock"

    |prevNode nextNode thisNode|

    thisNode := firstLink.
    [thisNode notNil] whileTrue:[
	nextNode := thisNode nextLink.
	(thisNode == aLink) ifTrue:[
	    prevNode isNil ifTrue:[
		firstLink := thisNode nextLink
	    ] ifFalse:[
		prevNode nextLink:(thisNode nextLink)
	    ].
	    (lastLink == thisNode) ifTrue:[
		thisNode nextLink isNil ifTrue:[
		    lastLink := prevNode
		] ifFalse:[
		    lastLink := thisNode nextLink
		]
	    ].
	    numberOfNodes := numberOfNodes - 1.
	    thisNode nextLink:nil.
	    ^ aLink
	].
	prevNode := thisNode.
	thisNode := nextNode
    ].
    ^ exceptionBlock value
!

removeFirst
    "remove and return the first node from the sequence"

    |link|

    firstLink isNil ifTrue:[
	self errorIsEmpty
    ] ifFalse:[
	link := firstLink.
	(firstLink == lastLink) ifTrue:[
	    firstLink := nil.
	    lastLink := nil
	] ifFalse:[
	    firstLink := firstLink nextLink
	].
	link nextLink:nil.
	numberOfNodes := numberOfNodes - 1
    ].
    ^ link
! !

!LinkedList methodsFor:'enumerating'!

do:aBlock
    "evaluate the argument, aBlock with 1 arg for every element in the list"

    |thisNode|

    thisNode := firstLink.
    [thisNode notNil] whileTrue:[
	aBlock value:thisNode.
	thisNode := thisNode nextLink
    ]
! !

!LinkedList methodsFor:'ininialization'!

initialize
    numberOfNodes := 0
! !

!LinkedList methodsFor:'queries'!

isEmpty
    "return true, if the collection is empty"

    ^ firstLink isNil
!

notEmpty
    "return true, if the collection is not empty"

    ^ firstLink notNil
!

size
    "return the size of the LinkedList i.e. the number of nodes"

    ^ numberOfNodes
! !

!LinkedList methodsFor:'testing'!

identityIndexOf:aLink startingAt:start 
    "search the collection for aLink, starting the search at index start;
     if found, return the index otherwise return 0. Here, index is defined
     as the link-nodes position in the list.
     The comparison is done using == 
     (i.e. equality test - not identity test)."

    |theNode idx "{ Class: SmallInteger }"|

    theNode := firstLink.
    idx := 1.
    [idx < start] whileTrue:[
	theNode isNil ifTrue:[^ 0].     "reached the end"
	theNode := theNode nextLink.
	idx := idx + 1.
    ].
    [theNode notNil] whileTrue:[
	(aLink == theNode) ifTrue:[^ idx].
	theNode := theNode nextLink.
	idx := idx + 1.
    ].                                  "reached the end"
    ^ 0

    "
     |l|

     l := LinkedList new.
     l indexOf:'hello'  
    "

    "
     |l v|

     l := LinkedList new.
     l add:(ValueLink new value:'one').
     l add:(ValueLink new value:'two').
     l add:(v := ValueLink new value:'hello').
     l identityIndexOf:v   
    "
!

indexOf:aLink startingAt:start 
    "search the collection for aLink, starting the search at index start;
     if found, return the index otherwise return 0. Here, index is defined
     as the link-nodes position in the list.
     The comparison is done using = (i.e. equality test - not identity test)."

    |theNode idx "{ Class: SmallInteger }"|

    theNode := firstLink.
    idx := 1.
    [idx < start] whileTrue:[
	theNode isNil ifTrue:[^ 0].     "reached the end"
	theNode := theNode nextLink.
	idx := idx + 1.
    ].
    [theNode notNil] whileTrue:[
	(aLink = theNode) ifTrue:[^ idx].
	theNode := theNode nextLink.
	idx := idx + 1.
    ].                                  "reached the end"
    ^ 0

    "
     |l|

     l := LinkedList new.
     l indexOf:'hello'  
    "

    "
     |l v|

     l := LinkedList new.
     l add:(ValueLink new value:'one').
     l add:(ValueLink new value:'two').
     l add:(v := ValueLink new value:'hello').
     l indexOf:v  
    "
! !