LinkList.st
author claus
Fri, 16 Jul 1993 11:39:45 +0200
changeset 1 a27a279701f8
child 3 24d81bf47225
permissions -rw-r--r--
Initial revision

"
 COPYRIGHT (c) 1989-93 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 nodeClass numberOfNodes'
       classVariableNames:''
       poolDictionaries:''
       category:'Collections-Sequenceable'
!

LinkedList comment:'

COPYRIGHT (c) 1989-93 by Claus Gittinger
              All Rights Reserved

this class implements an anchor to a list of Links.
The data itself is held in the Link elements (see Link and subclasses).

%W% %E%
'!

!LinkedList class methodsFor:'instance creation'!

new
    "create and return a new LinkedList"

    ^ super new initialize
! !

!LinkedList methodsFor:'ininialization'!

initialize
    numberOfNodes := 0
! !

!LinkedList methodsFor:'copying'!

deepCopy
    |newList|
    newList := self shallowCopy.
    newList setFirstNode:(firstLink deepCopy).
    newList setLastNode:(firstLink last).
    ^ newList
! !

!LinkedList methodsFor:'accessing'!

setFirstNode:aNode
    "set the first node to be the argument, aNode"

    firstLink := aNode
!

setLastNode:aNode
    "set the last node to be the argument, aNode"

    lastLink := aNode
!

first
    "return the first node in the list"

    ^ firstLink
!

last
    "return last node in the list"

    ^ lastLink
!

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

    ^ numberOfNodes
! !

!LinkedList methodsFor:'testing'!

includes:anObject
    "return true, if some nodes contents is anObject"

    |theNode|

    theNode := firstLink.
    [theNode notNil] whileTrue:[
        (anObject = theNode) ifTrue:[^ true].
        theNode := theNode nextLink
    ].
    ^ false
! !

!LinkedList methodsFor:'adding/removing elements'!

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
!

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 addLast:linkToAdd ].
    linkToAdd nextLink:(this nextLink).
    this nextLink:linkToAdd.
    ^ linkToAdd
!

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
        ].
        numberOfNodes := numberOfNodes - 1
    ].
    ^ link
!

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

    |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.
            ^ self
        ].
        prevNode := thisNode.
        thisNode := nextNode
    ].
    ^ exceptionBlock value
! !

!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
    ]
!

reverseDo:aBlock fromNode:aNode
    "helper for reverseDo:"

    aNode notNil ifTrue:[
        aNode nextLink notNil ifTrue:[
            self reverseDo:aBlock fromNode:(aNode nextLink)
        ].
        aBlock value:aNode
    ]
!

reverseDo:aBlock
    "evaluate the argument, aBlock with 1 arg for every element in the list
     in the reverse order"

    self reverseDo:aBlock fromNode:firstLink
! !