Interval.st
author claus
Fri, 16 Jul 1993 11:39:45 +0200
changeset 1 a27a279701f8
child 2 6526dde5f3ac
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:#Interval
       instanceVariableNames:'start stop step'
       classVariableNames:''
       poolDictionaries:''
       category:'Collections-Sequenceable'
!

Interval comment:'

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

Intervals represent a collection (or range) of numeric values specified by
a startValue, an endValue and a step. The elements are computed, not stored.
For example, the interval (1 to:5) containes the elements (1 2 3 4 5) and
(1 to:6 by:2) contains (1 3 5).


%W% %E%

written summer 89 by claus
'!

!Interval class methodsFor:'instance creation'!

from:start to:stop
    "return a new interval with elements from start
     to stop by 1"

    ^ self new
        setFrom:start 
        to:stop
        by:1
!

from:start to:stop by:step
    "return a new interval with elements from start
     to stop by step"

    ^ self new
        setFrom:start
        to:stop
        by:step
! !

!Interval methodsFor:'private'!

setFrom:startInteger to:stopInteger by:stepInteger
    start := startInteger.
    stop := stopInteger.
    step := stepInteger
! !

!Interval methodsFor:'accessing'!

first
    "return the first element of the collection"

    ^ start
!

start
    "return the first number of the range"

    ^ start
!

start:aNumber
    "set the first number of the range"

    start := aNumber
!

stop
    "return the end number of the range"

    ^ stop
!

stop:aNumber
    "set the end number of the range"

    stop := aNumber
!

step
    "return the step increment of the range"

    ^ step
!

step:aNumber
    "set the step increment of the range"

    step := aNumber
!

size
    "return the number of elements in the collection"

    (step < 0) ifTrue:[
        (start < stop) ifTrue:[
            ^ 0
        ].
        ^ stop - start // step + 1
    ].
    (stop < start) ifTrue:[
        ^ 0
    ].
    ^ stop - start // step + 1
!

at:index
    (index between:1 and:self size) ifTrue:[
        ^ start + (step * (index - 1))
    ].
    self errorSubscriptBounds:index
!

at:index put:anObject
    self error:'you cannot store into an interval'
! !

!Interval methodsFor:'adding/removing elements'!

add:newObject
    self error:'elements cannot be added to an interval'
!

remove:anObject
    self error:'elements cannot be removed from an interval'
! !

!Interval methodsFor:'private'!

species
    ^ OrderedCollection
! !
    
!Interval methodsFor:'enumeration'!

do:aBlock
    |aValue|

    aValue := start.
    step < 0 ifTrue:[
        [stop <= aValue] whileTrue:[
            aBlock value:aValue.
            aValue := aValue + step
        ]
    ] ifFalse:[
        [stop >= aValue] whileTrue:[
            aBlock value:aValue.
            aValue := aValue + step
        ]
    ]
!

select:aBlock
    "evaluate the argument, aBlock for every element in the collection
     and return a collection of all elements for which the block return
     true. redefined since SeqColl accesses the receiver with at:, which is
     slow for intervals."

    |newColl|

    newColl := OrderedCollection new:self size.
    self do:[:each |
        (aBlock value:each) ifTrue:[newColl add:each]
    ].
    ^ newColl
!

collect:aBlock
    "evaluate the argument, aBlock for every element in the collection
     and return a collection of the results - redefined since SeqColl
     accesses the receiver via at:, which is slow for intervals"

    |newCollection|

    newCollection := self species new:(self size).
    self do:[:each |
        newCollection add:(aBlock value:each)
    ].
    ^ newCollection
! !