Interval.st
author Claus Gittinger <cg@exept.de>
Tue, 22 Aug 2000 15:57:33 +0200
changeset 5557 f5f8d236027c
parent 5521 7cad30b0ade9
child 5672 bd82b2b8c930
permissions -rw-r--r--
category change

"
 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.
"

"{ Package: 'stx:libbasic' }"

SequenceableCollection subclass:#Interval
	instanceVariableNames:'start stop step'
	classVariableNames:''
	poolDictionaries:''
	category:'Collections-Sequenceable'
!

!Interval 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
"
    Intervals represent a collection (or range) of numeric values specified by
    a startValue, an endValue and a step. 
    The interesting thing is that 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).

    examples:

	(1 to:10) do:[:i | Transcript showCR:i]

      notice, that this is semantically equivalent to:

	1 to:10 do:[:i | Transcript showCR:i]

      however, the second is preferred, since loops using to:do: are
      much faster and do not create temporary garbage objects. 
      Therefore, Intervals are generally NOT used for this kind of loops.

	(1 to:10) asArray  

	(1 to:10 by:2) asOrderedCollection  

    [author:]
	Claus Gittinger
"
! !

!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:'accessing'!

at:index
    "return (i.e. compute) the index'th element"

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

at:index put:anObject
    "{ Pragma: +optSpace }"

    "catch at:put: message - intervals cannot store elements"

    self error:'you cannot store into an interval'
!

first
    "return the first element of the collection"

    (((step < 0) and:[start < stop])
    or:[(step > 0) and:[stop < start]]) ifTrue:[
        ^ self emptyCollectionError
    ].
    ^ start
!

increment 
    "alias for #step; for ST-80 compatibility"

    ^ step
!

last
    "return the last element of the collection"

    (((step < 0) and:[start < stop])
    or:[(step > 0) and:[stop < start]]) ifTrue:[
        ^ self emptyCollectionError
    ].
    ^ stop
!

start
    "return the first number of the range"

    ^ start
!

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

    start := aNumber
!

step
    "return the step increment of the range.
     OBSOLETE: 
	Please use #increment for ST-80 compatibility."

    ^ step
!

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

    step := aNumber
!

stop
    "return the end number of the range"

    ^ stop
!

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

    stop := aNumber
! !

!Interval methodsFor:'adding & removing'!

add:newObject
    "{ Pragma: +optSpace }"

    "catch add message - intervals cannot add elements"

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

remove:anObject
    "{ Pragma: +optSpace }"

    "catch remove message - intervals cannot remove elements"

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

!Interval methodsFor:'enumerating'!

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

    "
     (1 to:20) collect:[:i | i*i]
    "
!

do:aBlock
    "evaluate the argument, aBlock for every element in the
     receiver-interval. 
     Redefined since SeqColl accesses the receiver with at:, which is
     slow for intervals."

    |aValue iter|

    aValue := start.
    aValue isInteger ifTrue:[
        step < 0 ifTrue:[
            [stop <= aValue] whileTrue:[
                aBlock value:aValue.
                aValue := aValue + step
            ]
        ] ifFalse:[
            [stop >= aValue] whileTrue:[
                aBlock value:aValue.
                aValue := aValue + step
            ]
        ]
    ] ifFalse:[
        "/ the code below avoids rounding errors
        "/ to accumulate if floats are enumerated.
        iter := 1.
        step < 0 ifTrue:[
            [stop <= aValue] whileTrue:[
                aBlock value:aValue.
                aValue := start + (iter * step).
                iter := iter + 1.
            ]
        ] ifFalse:[
            [stop >= aValue] whileTrue:[
                aBlock value:aValue.
                aValue := start + (iter * step).
                iter := iter + 1.
            ]
        ]
    ]

    "
     1e7 to:1e7+1 by:0.25 do:[:v | Transcript showCR:v]
     1.0 to:2.0 by:0.25 do:[:v | Transcript showCR:v]
     2.0 to:1.0 by:-0.25 do:[:v | Transcript showCR:v]
    "
!

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 := self species new:(self size).
    self do:[:each |
	(aBlock value:each) ifTrue:[newColl add:each]
    ].
    ^ newColl

    "
     (1 to:20) select:[:i | i even]
    "
! !

!Interval methodsFor:'printing & storing'!

printOn:aStream
    "append a printed representation to aStream"

    start printOn:aStream.
    aStream nextPutAll:' to:'.
    stop printOn:aStream.
    step ~= 1 ifTrue:[
	aStream nextPutAll:' by:'.
	step printOn:aStream.
    ].

    "
     (1 to:10) printOn:Transcript
     (1 to:10 by:2) printOn:Transcript
     (1 to:10) printString
    "
!

storeOn:aStream
    "store a representation which can reconstruct the receiver to aStream"

    aStream nextPut:$(.
    self printOn:aStream.
    aStream nextPut:$).

    "
     (1 to:10) storeOn:Transcript
     (1 to:10 by:2) storeOn:Transcript
    "
! !

!Interval methodsFor:'private'!

setFrom:startInteger to:stopInteger by:stepInteger
    "set start, stop and step components"

    start := startInteger.
    stop := stopInteger.
    step := stepInteger
!

species
    "return the type of collection to be returned by collect, select etc."

    ^ OrderedCollection
! !

!Interval methodsFor:'queries'!

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

!Interval class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Interval.st,v 1.27 2000-08-22 13:56:51 cg Exp $'
! !