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

"{ Encoding: utf8 }"

"
 COPYRIGHT (c) 1996 by eXept Software AG
              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.
"
"{ Package: 'stx:libbasic2' }"

"{ NameSpace: Smalltalk }"

OrderedCollection subclass:#List
	instanceVariableNames:'dependents optionalAccessLock'
	classVariableNames:''
	poolDictionaries:''
	category:'Collections-Sequenceable'
!

!List class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1996 by eXept Software AG
              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
"
    Lists are mostly like OrderedCollections, but keep their dependents
    locally (which is adding a bit of performance - not functionality).
    In addition, special change notifications are emitted, whenever
    a list's contents is changed.
    Some views (SelectionIn*View and DataSetView) react specially on
    those messages and perform optimized updates.
    (the change messages pass the range-of-change as parameter).

    In ST/X, most functionality is already provided by OrderedCollection,
    so there is not much new stuff found here.
    It has been mostly provided, for ST-80 compatibility,
    where it adds sorting capabilities.

    New: 
        if the optional optionalAccessLock is set, all operations
        are protected by a critical region.
        (i.e. the List is a SynchronizedCollection)
        
    [caveat:]
        'List' is probably a bad name, which may confuse beginners.
        I have nothing in common with LinkedLists.
        Instances are just regular ordered collections, with the added benefit of
        sending out information about changes, and an optional synchronization lock.
        Thus, they can be used as a model of textviews or selection list views,
        which need to redraw whenever the contents of the list changes.
        (and Lists not only send out change notifications when modified,
         but also include information about the range of changed elements.
         So the view can optimize its redraws)
        
    [see also:]
        Array OrderedCollection

    [author:]
        Claus Gittinger
"
! !

!List methodsFor:'accessing'!

at:anIndex put:anObject
    "set the element at index, to be anIndex.
     Return anObject (sigh).
     In contrast to OrderedCollection, Lists allow putting an object
     right after the last element and auto-grow in this case;
     however, putting 2 or more indices after the last element is 
     reported as an error."

    |idx "{ Class: SmallInteger }"|

    self possiblySynchronized:[
        idx := anIndex + firstIndex - 1.
        ((anIndex < 1) or:[idx > lastIndex]) ifTrue:[
            idx == (lastIndex+1) ifTrue:[
                self makeRoomAtLast.
                lastIndex := lastIndex + 1.
            ] ifFalse:[
                ^ self subscriptBoundsError:anIndex
            ]
        ].

        contentsArray basicAt:idx put:anObject.
        dependents notNil ifTrue:[self changed:#at: with:anIndex].
    ].
    ^ anObject

    "Modified: / 28-01-1998 / 16:44:49 / cg"
    "Modified: / 01-08-2018 / 11:46:40 / Claus Gittinger"
!

list
    ^ self
!

synchronizationSemaphore
    "return a synchronization semaphore for myself"
    
    optionalAccessLock notNil ifTrue:[
        ^ optionalAccessLock
    ].
    ^ super synchronizationSemaphore.

    "Created: / 01-08-2018 / 13:22:45 / Claus Gittinger"
! !

!List methodsFor:'adding & removing'!

add:anObject
    "add the argument, anObject to the end of the collection
     Return the argument, anObject."

    self possiblySynchronized:[
        super add:anObject.
        dependents notNil ifTrue:[self changed:#insert: with:(self size)].
    ].
    ^ anObject

    "Modified: / 29-01-1998 / 10:52:32 / cg"
    "Modified: / 01-08-2018 / 11:46:58 / Claus Gittinger"
!

add:anObject after:oldObject
    "insert the argument, newObject after oldObject.
     If oldObject is not in the receiver, report an error,
     otherwise return the argument, anObject."

    self possiblySynchronized:[
        super add:anObject after:oldObject.
    ].

    "Created: / 19-02-2019 / 23:48:35 / Claus Gittinger"
!

add:anObject beforeIndex:index
    "add the argument, anObject to the end of the collection.
     Return the receiver (sigh - ST-80 compatibility)."

    self possiblySynchronized:[
        super add:anObject beforeIndex:index.
        dependents notNil ifTrue:[
            self changed:#insert: with:index
        ].
    ].

    "Modified (format): / 01-08-2018 / 11:47:24 / Claus Gittinger"
!

addAll:aCollection beforeIndex:index
    "insert all elements of the argument, anObject to become located at index.
     The collection may be unordered, but then the order of the sliced-in elements
     is undefined.
     Return the receiver."

    self possiblySynchronized:[
        super addAll:aCollection beforeIndex:index.
        dependents notNil ifTrue:[
            self changed: #insertCollection: with:(Array with:index with:(aCollection size))
        ]
    ]

    "Modified: / 01-08-2018 / 11:47:17 / Claus Gittinger"
!

addAll:aCollection from:startIndex to:endIndex beforeIndex:index
    "insert elements start to stop from the argument
     Return the receiver."

    self possiblySynchronized:[
        super addAll:aCollection from:startIndex to:endIndex beforeIndex:index.
        dependents notNil ifTrue:[
            self changed: #insertCollection: with:(Array with:index with:(endIndex - startIndex + 1))
        ]
    ]

    "Modified: / 29-01-1998 / 10:52:57 / cg"
    "Modified: / 30-07-2018 / 11:16:31 / Stefan Vogel"
    "Modified: / 01-08-2018 / 11:47:38 / Claus Gittinger"
!

addAllLast:aCollection
    "add all elements of the argument, aCollection to the end of the collection.
     Return the argument, aCollection."

    self possiblySynchronized:[
        self addAll:aCollection beforeIndex:self size + 1.
    ].    
    ^ aCollection

    "Modified: / 01-08-2018 / 11:47:55 / Claus Gittinger"
!

addFirst:anObject
    "add the argument, anObject to the beginning of the collection.
     Return the argument, anObject."

    self possiblySynchronized:[
        super addFirst:anObject.
        dependents notNil ifTrue:[self changed:#insert: with:1].
    ].
    ^ anObject

    "Modified: / 29-01-1998 / 10:53:09 / cg"
    "Modified: / 01-08-2018 / 11:48:05 / Claus Gittinger"
!

clearContents
    "remove all elements from the collection but keep the contentsArray.
     Useful for huge lists, if the contents will be rebuild soon (using #add:) 
     to a size which is similar to the lists current size.
     Returns the receiver."

    self possiblySynchronized:[
        |prevSize|

        prevSize := self size.
        super clearContents.

        dependents notNil ifTrue:[
            prevSize ~~ 0 ifTrue:[
                self changed:#removeFrom: with:(Array with:1 with:prevSize)
            ]
        ]
     ]

    "Modified (format): / 01-08-2018 / 11:51:29 / Claus Gittinger"
!

dropLast:n
    "remove the last n elements from the receiver collection. 
     Return the receiver."

    self possiblySynchronized:[
        | stop |
        stop := self size.
        super dropLast:n.
        dependents notNil ifTrue:[
            self changed:#removeFrom: with:(Array with:(stop - n + 1) with:stop).
        ].
    ].
    ^ self

    "Created: / 03-04-2019 / 12:40:35 / Claus Gittinger"
!

removeAll
    "remove all elements from the collection.
     Returns the receiver."

    self possiblySynchronized:[
        |prevSize|

        prevSize := self size.
        super removeAll.

        dependents notNil ifTrue:[
            prevSize ~~ 0 ifTrue:[
               self changed:#removeFrom: with:(Array with:1 with:prevSize)
           ]
        ]
    ]

    "Modified: / 29-01-1998 / 10:53:28 / cg"
    "Modified (format): / 01-08-2018 / 11:51:21 / Claus Gittinger"
!

removeAllSuchThat:aBlock
    "remove all elements that meet a test criteria as specified in aBlock.
     The argument, aBlock is evaluated for successive elements and all those,
     for which it returns true, are removed.
     Destructive: modifies the receiver.
     Return a collection containing the removed elements."

    |removedElements|

    self possiblySynchronized:[
        removedElements := super removeAllSuchThat:aBlock.
        removedElements notEmpty ifTrue:[
            self changed.
        ].
    ].
    ^ removedElements.

    "Modified: / 01-08-2018 / 11:49:44 / Claus Gittinger"
!

removeFirst
    "remove the first element from the collection; return the element."

    |deletedObject|

    self possiblySynchronized:[
        deletedObject := super removeFirst.
        dependents notNil ifTrue:[self changed:#remove: with:1].
    ].
    ^ deletedObject

    "Modified: / 29-01-1998 / 10:53:36 / cg"
    "Modified: / 01-08-2018 / 11:49:58 / Claus Gittinger"
!

removeFirst:n
    "remove the first n elements from the collection; 
     Return a collection containing the removed elements."

    |deletedObjects|

    self possiblySynchronized:[
        deletedObjects := super removeFirst:n.
        dependents notNil ifTrue:[self changed:#removeFrom: with:(Array with:1 with:n)].
    ].
    ^ deletedObjects

    "Modified: / 29-01-1998 / 10:53:40 / cg"
    "Modified: / 01-08-2018 / 11:50:10 / Claus Gittinger"
!

removeFirstIfAbsent:exceptionBlock
    "remove the first element from the collection; return the element.
     If there is no element in the receiver collection, return the value from
     exceptionBlock."

    self possiblySynchronized:[
        self notEmpty ifTrue:[ ^ self removeFirst ].
    ].
    ^ exceptionBlock value

    "Modified: / 21-10-2006 / 23:03:46 / cg"
    "Modified: / 11-04-2018 / 11:52:30 / stefan"
    "Modified: / 01-08-2018 / 11:50:26 / Claus Gittinger"
!

removeFromIndex:startIndex toIndex:stopIndex
    "remove the elements stored under startIndex up to and including
     the elements under stopIndex.
     Return the receiver.
     Returning the receiver here is a historic leftover - it may change."

    |ret|

    stopIndex < startIndex ifTrue:[^ self].

    self possiblySynchronized:[
        ret := super removeFromIndex:startIndex toIndex:stopIndex.
        dependents notNil ifTrue:[
            self changed:#removeFrom: with:(Array with:startIndex with:stopIndex).
        ].
    ].    
    ^ ret

    "Modified: / 29-01-1998 / 10:54:03 / cg"
    "Modified: / 01-08-2018 / 11:50:42 / Claus Gittinger"
!

removeIdentical:anObject ifAbsent:exceptionBlock
    "remove the first element which is identical to anObject;
     if found, remove and return it; 
     if not, return the value from evaluating exceptionBlock.
     Uses identity compare (==) to search for the element."

    self possiblySynchronized:[
        |index|

        index := self identityIndexOf:anObject.

        index == 0 ifTrue:[ ^ exceptionBlock value ].
        self removeFromIndex:index toIndex:index.
    ].    
    ^ anObject

    "Modified: / 21-10-2006 / 23:03:29 / cg"
    "Modified (format): / 01-08-2018 / 11:51:07 / Claus Gittinger"
!

removeLast
    "remove the last element from the collection; return the element"

    |deletedObject|

    self possiblySynchronized:[
        deletedObject :=  super removeLast.
        dependents notNil ifTrue:[self changed:#remove: with:(1 + self size)].
    ].
    ^ deletedObject

    "Modified: / 29-01-1998 / 10:54:15 / cg"
    "Modified: / 01-08-2018 / 11:51:51 / Claus Gittinger"
!

removeLast:n
    "remove the last n elements from the receiver collection. 
     Return a collection of removed elements."

    |deletedObjects|

    self possiblySynchronized:[
        | stop |
        stop := self size.
        deletedObjects := super removeLast:n.
        dependents notNil ifTrue:[
            self changed:#removeFrom: with:(Array with:(stop - n + 1) with:stop).
        ].
    ].
    ^ deletedObjects

    "Modified: / 29-01-1998 / 10:54:25 / cg"
    "Modified: / 01-08-2018 / 11:52:10 / Claus Gittinger"
!

removeLastIfAbsent:exceptionBlock
    "remove the last element from the collection; return the element.
     If there is no element in the receiver collection, return the value from
     exceptionBlock."

    self possiblySynchronized:[
        self notEmpty ifTrue:[ ^ self removeLast ].
    ].    
    ^ exceptionBlock value

    "Modified: / 21-10-2006 / 23:03:53 / cg"
    "Modified: / 30-07-2018 / 11:12:56 / Stefan Vogel"
    "Modified: / 01-08-2018 / 11:52:25 / Claus Gittinger"
!

reset
    "logically remove all elements from the collection.
     That's almost the same as #removeAll, but keeps the contentsArray.
     Returns the receiver."

    self possiblySynchronized:[
        |prevSize|

        prevSize := self size.
        super reset.

        dependents notNil ifTrue:[
            prevSize ~~ 0 ifTrue:[
               self changed:#removeFrom: with:(Array with:1 with:prevSize)
           ]
        ].
    ].

    "Modified: / 01-08-2018 / 11:52:46 / Claus Gittinger"
! !

!List methodsFor:'converting'!

asList
    ^ self

    "Created: 14.2.1997 / 16:25:55 / cg"
!

asSharedCollection
    "return a shared collection on the receiver.
     If the receiver is already synchronized, itself is returned. 
     This implements synchronized (i.e. mutually excluded) access to me.
     Use this for safe access when multiple processes access me concurrently."

    optionalAccessLock notNil ifTrue:[
        "I am alreay protected against concurrent access"
        ^ self
    ].
    
    ^ (List withAll:self)
            beSynchronized;
            yourself.

    "Created: / 01-08-2018 / 11:54:26 / Claus Gittinger"
    "Modified (format): / 01-08-2018 / 15:07:20 / Stefan Vogel"
    "Modified (format): / 02-02-2019 / 19:26:04 / Claus Gittinger"
! !

!List methodsFor:'copying'!

skipInstvarIndexInDeepCopy:index
    "a helper for deepCopy; only indices for which this method returns
     false are copied in a deep copy."

    ^ index == 4    "/ skip dependents
! !

!List methodsFor:'dependents access'!

addDependent:anObject
    "make the argument, anObject be a dependent of the receiver."

    ^ self addNonWeakDependent:anObject
!

dependents 
    "return the dependents of the receiver"

    ^ dependents ? #()

    "Created: / 14.2.1997 / 16:05:49 / cg"
    "Modified: / 27.10.1997 / 19:37:33 / cg"
!

dependents:aCollection
    "set the dependents of the receiver"

    aCollection size == 0 ifTrue:[
        dependents := nil
    ] ifFalse:[
        dependents := aCollection.
    ].

    "Created: / 14.2.1997 / 16:05:58 / cg"
    "Modified: / 29.1.1998 / 10:54:52 / cg"
!

nonWeakDependents
    "return a Collection of dependents - empty if there is none.
     Since all dependencies are nonWeak in List, this is a dummy."

    ^ dependents ? #()
!

nonWeakDependents:newDeps
    "return a Collection of dependents - empty if there is none.
     Since all dependencies are nonWeak in List, this is a dummy."

    ^ self dependents:newDeps

    "Created: / 19.4.1996 / 10:29:43 / cg"
    "Modified: / 30.1.1998 / 14:06:12 / cg"
!

removeDependent:anObject
    "make the argument, anObject be independent of the receiver.
     Since all dependencies are nonWeak in Model, this is simply
     forwarded to removeDependent:"

    ^ self removeNonWeakDependent:anObject
! !

!List methodsFor:'filling & replacing'!

contents:aCollection
    "replace all elements in the receiver by aCollection,
     Redefined - can be done faster"

    |oldSize newSize|

    aCollection isSequenceable ifFalse:[
       ^ super contents:aCollection
    ].

    self possiblySynchronized:[
        oldSize := self size.
        newSize := aCollection size.

        newSize < oldSize ifTrue:[
           self replaceFrom:1 to:newSize with:aCollection startingAt:1.
           self removeFromIndex:newSize+1 toIndex:oldSize.
        ] ifFalse:[
           newSize > oldSize ifTrue:[
               oldSize == 0 ifTrue:[
                   self addAll:aCollection       
               ] ifFalse:[
                   self replaceFrom:1 to:oldSize with:aCollection startingAt:1.
                   self addAll:aCollection from:oldSize+1 to:newSize beforeIndex:oldSize+1        
               ]
           ] ifFalse:[
               "/ same size
               oldSize ~~ 0 ifTrue:[
                   self replaceFrom:1 to:newSize with:aCollection startingAt:1.
               ]
           ]
        ].
    ].
    
    "
      |l|
      l := List new.
      l contents:#(1 2 3 4 5).
      l        

      |l|
      l := List new.
      l addAll:#(1 2 3 4 5).
      l contents:#(10 20 30).
      l       

      |l|
      l := List new.
      l addAll:#(1 2 3 4 5).
      l contents:#(10 20 30 40 50 60 70 80).
      l      

      |l|
      l := List new.
      l addAll:#(1 2 3 4 5).
      l contents:#(10 20 30 40 50).
      l      
    "

    "Modified: / 01-08-2018 / 11:55:20 / Claus Gittinger"
!

list:aCollection
    "replace all elements in the receiver by aCollection.
     For compatibility with other smalltalks 
     (allows List to be sometimes used as a ListPresenter in ported Dolphin apps)"

    self contents:aCollection

    "
     |l|
     l := List new.
     l list:#(1 2 3 4 5).
     l        

     |l|
     l := List new.
     l addAll:#(1 2 3 4 5).
     l list:#(10 20 30).
     l       

     |l|
     l := List new.
     l addAll:#(1 2 3 4 5).
     l list:#(10 20 30 40 50 60 70 80).
     l      

     |l|
     l := List new.
     l addAll:#(1 2 3 4 5).
     l list:#(10 20 30 40 50).
     l      
    "
!

replaceFrom:start to:stop with:aCollection startingAt:repStart
    "replace elements in the receiver between index start and stop,
     with elements  taken from replacementCollection starting at repStart.
     Redefined - can be done faster"

    stop < start ifTrue:[^ self].

    self possiblySynchronized:[
        "/ see if there is really any change involved
        (self sameContentsFrom:start to:stop as:aCollection startingAt:repStart) ifTrue:[
            ^ self  "/ avoids useless change notifications
        ].

        super replaceFrom:start to:stop with:aCollection startingAt:repStart.

        dependents notNil ifTrue:[
            self changed:#replace: with:(Array with:start with:stop)
        ].
    ].

    "Modified: / 20-05-1998 / 15:20:17 / cg"
    "Modified: / 01-08-2018 / 11:55:41 / Claus Gittinger"
!

setContents:aCollection
    "replace the receiver's underlying collection by aCollection"

    self possiblySynchronized:[
        aCollection isSequenceable ifFalse:[
           ^ super contents:aCollection
        ].

        contentsArray := aCollection.
        firstIndex := 1.
        lastIndex := aCollection size.
        self changed.
    ].

    "Modified: / 01-08-2018 / 11:56:01 / Claus Gittinger"
! !

!List methodsFor:'private'!

possiblySynchronized:aBlock
    optionalAccessLock notNil ifTrue:[
        ^ optionalAccessLock synchronized:aBlock.
    ].
    ^ aBlock value.

    "Created: / 01-08-2018 / 11:46:01 / Claus Gittinger"
!

synchronized:aBlock
    "a shortcut, if the sync-sema is already present;
     return the value from aBlock"
    
    optionalAccessLock notNil ifTrue:[
        ^ optionalAccessLock synchronized:aBlock.
    ].
    ^ super synchronized:aBlock.

    "Created: / 02-02-2019 / 19:23:27 / Claus Gittinger"
    "Modified (comment): / 07-06-2019 / 13:51:10 / Claus Gittinger"
! !

!List methodsFor:'setup'!

beSynchronized
    "make the receiver a synchronized List"
    
    |wasBlocked|

    optionalAccessLock isNil ifTrue:[
        wasBlocked := OperatingSystem blockInterrupts.
        optionalAccessLock isNil ifTrue:[
            "already a registered synchronizationSemaphore for myself in Object? 
             - then use it!!"
            optionalAccessLock := SynchronizationSemaphores removeKey:self ifAbsent:[].
            optionalAccessLock isNil ifTrue:[
                optionalAccessLock := RecursionLock name:self className.
            ].
        ].
        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
    ].

    "
        |list oldSema|

        list := List new.
        list synchronized:[list add:1].
        oldSema := list synchronizationSemaphore.
        list beSynchronized.
        self assert:oldSema == list synchronizationSemaphore.
        oldSema
    "

    "Created: / 01-08-2018 / 11:44:37 / Claus Gittinger"
    "Modified (comment): / 01-08-2018 / 15:10:45 / Stefan Vogel"
! !

!List methodsFor:'testing'!

isList
    "return true, if the receiver is some kind of list collection;
     true is returned here - the method is redefined from Object."

    ^ true

    "Modified: / 11.2.2000 / 01:37:36 / cg"
! !

!List class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !