GeometricSeries.st
author Claus Gittinger <cg@exept.de>
Sat, 02 May 2020 21:40:13 +0200
changeset 5476 7355a4b11cb6
parent 5079 aa82caad8dbc
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) 2000 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 }"

ReadOnlySequenceableCollection subclass:#GeometricSeries
	instanceVariableNames:'start stop factor'
	classVariableNames:''
	poolDictionaries:''
	category:'Collections-Sequenceable'
!

!GeometricSeries class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2000 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
"
    Much like intervals (which have a constant difference between elements), 
    these have a constant factor between them.
    GeometricSeries represent a collection (or range) of values specified by
    a startValue, an endValue and a *factor*. 
    Like with intervals, the elements are computed, not stored.
    For example, 
        the GeometricSeries (1 to:100 byFactor:2) contains the elements (1 2 4 8 16 32 64).
        and GeometricSeries (1 to:(1/100) byFactor:(1/2)) contains the elements (1 1/2 1/4 1/8 1/16 1/32 1/64).

    examples:

        (1 to:100 byFactor:2) do:[:i | Transcript showCR:i]
        (1 to:100 byFactor:1.1) do:[:i | Transcript showCR:i]
        (1 to:100 byFactor:2) asArray  
        (1 to:128 byFactor:2) asArray  
        (128 to:2 byFactor:(1/2)) asArray  

        (1 to:128 byFactor:2) sum
        (1 to:128 byFactor:2) asArray sum    
        
    [author:]
        Claus Gittinger
"
! !

!GeometricSeries class methodsFor:'instance creation'!

from:start to:stop byFactor:factor
    "return a new geometric series with elements from start
     to stop by a factor"

    ^ self new setFrom:start to:stop byFactor:factor


! !

!GeometricSeries methodsFor:'accessing'!

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

    (index between:1 and:self size) ifTrue:[
        ^ start * (factor raisedToInteger: (index - 1))
    ].
    ^ self subscriptBoundsError:index

    "
     (1 to:128 byFactor:2) do:[:v | Transcript showCR:v]
     (1 to:128 byFactor:2) at:1.
     (1 to:128 byFactor:2) at:2.
     (1 to:128 byFactor:2) at:3.
     (1 to:128 byFactor:2) last.  
     (1 to:100 byFactor:2) last.  

     (16 to:1 byFactor:(1/2)) do:[:v | Transcript showCR:v]
     (16 to:1 byFactor:(1/2)) at:1.
     (16 to:1 byFactor:(1/2)) at:2.
     (16 to:1 byFactor:(1/2)) at:3.
     (16 to:1 byFactor:(1/2)) last.
     (16 to:3 byFactor:(1/2)) last.    
    "

    "Created: / 22-07-2019 / 14:49:12 / Claus Gittinger"
!

first
    ^ start

    "
     (1 to:100 byFactor:2) first    
     (10 to:100 byFactor:3) first    
     (100 to:10 byFactor:1/3) first    
    "

    "Created: / 31.10.2001 / 15:06:31 / cg"
!

last
    |n last|

    n := (stop/start) log:factor.
    n := n truncated asInteger.
    ^ start * (factor raisedToInteger:n).

    "
     (1 to:100 byFactor:2) last    
     (1 to:100 byFactor:3) last     
     (10 to:100 byFactor:3) last    
     (100 to:10 byFactor:1/3) last    
     (100 to:1 byFactor:1/2) last    

     (1 to:100 byFactor:2.0) last    
     (1 to:64.0 byFactor:2.0) last    
     (1 to:100 byFactor:3.0) last     
     (10 to:100.0 byFactor:3) last    
     (100 to:10.0 byFactor:0.3) last    
     (100 to:3 byFactor:1/2) last    
     (100 to:3 byFactor:0.5) last    
    "

    "Created: / 31.10.2001 / 15:06:31 / cg"
! !

!GeometricSeries methodsFor:'enumerating'!

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

    |aValue iter|

    aValue := start.
    (aValue isLimitedPrecisionReal or:[factor isLimitedPrecisionReal]) ifFalse:[
        factor < 1 ifTrue:[
            [stop <= aValue] whileTrue:[
                aBlock value:aValue.
                aValue := aValue * factor
            ]
        ] ifFalse:[
            [stop >= aValue] whileTrue:[
                aBlock value:aValue.
                aValue := aValue * factor
            ]
        ]
    ] ifTrue:[
        "/ the code below tries to avoid rounding errors
        "/ to accumulate if floats are enumerated.
        iter := 1.
        factor < 1 ifTrue:[
            [stop <= aValue] whileTrue:[
                aBlock value:aValue.
                aValue := start * (factor raisedTo:iter).
                iter := iter + 1.
            ]
        ] ifFalse:[
            [stop >= aValue] whileTrue:[
                aBlock value:aValue.
                aValue := start * (factor raisedTo:iter).
                iter := iter + 1.
            ]
        ]
    ]

    "
     (1 to:128 byFactor:2) do:[:v | Transcript showCR:v]
     (16 to:1 byFactor:(1/2)) do:[:v | Transcript showCR:v]
     (1.0 to:128.0 byFactor:2) do:[:v | Transcript showCR:v]

     (GeometricSeries from:1 to:128 byFactor:2) do:[:v | Transcript showCR:v]
    "
! !

!GeometricSeries methodsFor:'printing & storing'!

printOn:aStream
    "append a printed representation to aStream"

    start printOn:aStream.
    aStream nextPutAll:' to:'.
    stop printOn:aStream.
    aStream nextPutAll:' byFactor:'.
    factor printOn:aStream.

!

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

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


! !

!GeometricSeries methodsFor:'private'!

setFrom:startVal to:stopVal byFactor:factorVal
    "set start, stop and factor components"

    start := startVal.
    stop := stopVal.
    factor := factorVal


!

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

    ^ OrderedCollection

! !

!GeometricSeries methodsFor:'queries'!

size
    |n last|

    n := (stop/start) log:factor.
    n := n truncated asInteger.
    last := start * (factor raisedToInteger:n).
    ^ n + 1

"/    cnt := 0.
"/    self do:[:each | cnt := cnt + 1].
"/    ^ cnt

    "
     (1 to:100 byFactor:2) size    
     (1 to:100 byFactor:3) size     
     (10 to:100 byFactor:3) size    
     (100 to:10 byFactor:1/3) size    
     (100 to:1 byFactor:1/2) size    

     (1 to:100 byFactor:2.0) size    
     (1 to:64.0 byFactor:2.0) size    
     (1 to:100 byFactor:3.0) size     
     (10 to:100.0 byFactor:3) size    
     (100 to:10.0 byFactor:0.3) size    
     (100 to:3 byFactor:1/2) size    
     (100 to:3 byFactor:0.5) size    
    "

    "Created: / 31.10.2001 / 15:06:31 / cg"
! !

!GeometricSeries class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !