Interval.st
author claus
Mon, 08 May 1995 05:31:14 +0200
changeset 339 e8658d38abfb
parent 328 7b542c0bf1dd
child 379 5b5a130ccd09
permissions -rw-r--r--
.

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

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

Interval comment:'
COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libbasic/Interval.st,v 1.14 1995-05-08 03:29:37 claus Exp $
'!

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

version
"
$Header: /cvs/stx/stx/libbasic/Interval.st,v 1.14 1995-05-08 03:29:37 claus Exp $
"
!

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

!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
    "set start, stop and step components"

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

!Interval methodsFor:'accessing'!

first
    "return the first element of the collection"

    ^ start
!

last
    "return the last element of the collection"

    ^ stop
!

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
!

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

    ^ step
!

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
!

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
    "return (i.e. compute) the index'th element"

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

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

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

!Interval methodsFor:'adding/removing elements'!

add:newObject
    "catch add message - intervals cannot add elements"

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

remove:anObject
    "catch remove message - intervals cannot remove elements"

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

!Interval methodsFor:'private'!

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

    ^ OrderedCollection
! !
    
!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:'enumerating'!

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|

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

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

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