SkipList.st
author Claus Gittinger <cg@exept.de>
Sat, 02 May 2020 21:40:13 +0200
changeset 5476 7355a4b11cb6
parent 4396 e84a571deedd
permissions -rw-r--r--
#FEATURE by cg class: Socket class added: #newTCPclientToHost:port:domain:domainOrder:withTimeout: changed: #newTCPclientToHost:port:domain:withTimeout:

"{ Package: 'stx:libbasic2' }"

"{ NameSpace: Smalltalk }"

Collection subclass:#SkipList
	instanceVariableNames:'sortBlock pointers numElements level splice'
	classVariableNames:'Rand'
	poolDictionaries:''
	category:'Collections-Ordered-Trees'
!

SkipList comment:'From "Skip Lists: A Probabilistic Alternative to Balanced Trees" by William Pugh ( http://epaperpress.com/sortsearch/download/skiplist.pdf ):

"Skip lists are a data structure that can be used in place of balanced trees.  Skip lists use probabilistic balancing rather than strictly enforcing balancing and as a result the algorithms for insertion and deletion in skip lists are much simpler and significantly faster than equivalent algorithms for balanced trees."

Notes:

The elements of the skip list must implement #< or you must provide a sort block.

'
!

!SkipList class methodsFor:'documentation'!

documentation
"
    From 'Skip Lists: A Probabilistic Alternative to Balanced Trees' by William Pugh 
    ( http://epaperpress.com/sortsearch/download/skiplist.pdf ):

    Skip lists are a data structure that can be used in place of balanced trees.  
    Skip lists use probabilistic balancing rather than strictly enforcing balancing 
    and as a result the algorithms for insertion and deletion in skip lists are much simpler 
    and significantly faster than equivalent algorithms for balanced trees.

    Notes:

    The elements of the skip list must implement #< or you must provide a sort block.
"
! !

!SkipList class methodsFor:'instance creation'!

maxLevel: maxLevel
	"
	SkipList maxLevel: 5
	"
	^ super new initialize: maxLevel
!

maxLevel: anInteger sortBlock: aBlock
	^ (self maxLevel: anInteger) sortBlock: aBlock
!

new
	"
	SkipList new
	"
	^ super new initialize: 10
!

new: anInteger
	^ self maxLevel: (anInteger log: 2) ceiling
!

new: anInteger sortBlock: aBlock
	^ (self new: anInteger) sortBlock: aBlock
!

sortBlock: aBlock
	^ self new sortBlock: aBlock
! !

!SkipList methodsFor:'accessing'!

level
	^ level
!

maxLevel
	^ pointers size
!

maxLevel: n
        | newLevel oldPointers |
        newLevel := n max:level.
        oldPointers := pointers.
        pointers := Array new:newLevel.
        splice := Array new:newLevel.
        1 to: level do: [:i | pointers at: i put: (oldPointers at: i)]

    "Modified (format): / 18-06-2017 / 17:42:51 / cg"
!

size
	^ numElements
!

sortBlock
	^ sortBlock
!

sortBlock: aBlock
        sortBlock := aBlock

    "Modified (format): / 18-06-2017 / 17:44:44 / cg"
! !

!SkipList methodsFor:'adding'!

add: element 
	self add: element ifPresent: nil.
	^ element
!

add: element ifPresent: aBlock
        | node lvl s |
        node := self search:element updating:splice.
        node notNil ifTrue: [aBlock notNil ifTrue: [^ aBlock value: node]].
        lvl := self randomLevel.
        node := SkipListNode on:element level:lvl.
        level + 1 to: lvl do: [:i | splice at: i put: self].
        1 to: lvl do: [:i |
                                s := splice at:i.
                                node atForward: i put: (s forward: i).
                                s atForward: i put: node].
        numElements := numElements + 1.
        splice atAllPut: nil.
        ^ element

    "Modified: / 18-06-2017 / 17:32:23 / cg"
! !

!SkipList methodsFor:'element comparison'!

is: element1 equalTo: element2
	^ element1 = element2
! !

!SkipList methodsFor:'enumerating'!

do: aBlock
	self nodesDo: [:node | aBlock value: node object]
! !

!SkipList methodsFor:'initialization'!

initialize: maxLevel
        pointers := Array new:maxLevel.
        splice := Array new:maxLevel.
        numElements := 0.
        level := 0.
        Rand ifNil: [Rand := RandomGenerator new]

    "Modified: / 18-06-2017 / 17:40:56 / cg"
! !

!SkipList methodsFor:'node enumeration'!

nodesDo: aBlock
        | node |
        node := pointers first.
        [node notNil]
                whileTrue:
                        [aBlock value: node.
                        node := node next]

    "Modified (format): / 18-06-2017 / 17:31:41 / cg"
! !

!SkipList methodsFor:'private'!

atForward: i put: node
        level := node
                ifNil: [pointers findLast: [:n | n notNil]]
                ifNotNil: [level max: i].
        ^ pointers at: i put: node

    "Modified (format): / 18-06-2017 / 17:32:30 / cg"
!

forward: i 
	^ pointers at: i
!

is: node before: element 
        | object |
        node isNil ifTrue: [^ false].
        object := node object.
        ^ sortBlock isNil 
            ifTrue: [object < element]
            ifFalse: [
                (self is: object equalTo: element) 
                    ifTrue: [ false]
                    ifFalse:[ sortBlock value: object value: element ]
            ]

    "Modified: / 18-06-2017 / 17:42:31 / cg"
!

is: node theNodeFor: element 
        node isNil ifTrue: [^ false].
        node == self ifTrue: [^ false].
        ^ self is: node object equalTo: element

    "Modified: / 18-06-2017 / 17:42:42 / cg"
!

next
	^ pointers first
!

randomLevel
        | p answer max |
        p := 0.5.
        answer := 1.
        max := self maxLevel.
        [Rand next < p and: [answer < max]]
                whileTrue: [answer := answer + 1].
        ^ answer

    "Modified (format): / 18-06-2017 / 17:42:59 / cg"
!

search: element updating: array
        | node forward |
        node := self.
        level to: 1 by: -1 do: [:i |
                        [forward := node forward: i.
                        self is: forward before: element] whileTrue: [node := forward].
                        "At this point: node < element <= forward"
                        array ifNotNil: [array at: i put: node]].
        node := node next.
        ^ (self is: node theNodeFor: element) 
                ifTrue: [node]
                ifFalse:[nil]

    "Modified: / 18-06-2017 / 17:44:37 / cg"
! !

!SkipList methodsFor:'removing'!

remove: element ifAbsent: aBlock
        | node i s |
        node := self search:element updating:splice.
        node isNil ifTrue:[
              ^ aBlock value
        ].
        i := 1.
        [s := splice at:i.
        i <= level and: [(s forward: i) == node]] whileTrue: [
            s atForward: i put: (node forward: i).
            i := i + 1
        ].
        numElements := numElements - 1.
        splice atAllPut: nil.
        ^ node object

    "Modified (format): / 18-06-2017 / 17:43:30 / cg"
!

removeAll
        pointers atAllPut: nil.
        splice atAllPut: nil.
        numElements := 0.
        level := 0.

    "Modified (format): / 18-06-2017 / 17:43:39 / cg"
! !

!SkipList methodsFor:'testing'!

includes: element
	^ (self search: element updating: nil) notNil
!

isEmpty
	^ numElements = 0
! !

!SkipList class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !