Interval>>includes:

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
36 messages Options
12
Reply | Threaded
Open this post in threaded view
|

Interval>>includes:

Ian Bartholomew
Interval>>includes: inherits from Collection which gives it a rather
sub-optimal performance - it iterates through the complete range looking for
the target. The following works a bit faster and provides, I think, the same
results.

includes: aNumber
    ^aNumber >= (self first min: self last)
            and: [aNumber <= (self first max: self last)]

Regards
    Ian


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

Eric Winger-4
Hmmm....what about:

i := Interval from: 1 to: 10 by: 2.
i includes: 4.

Eric

Ian Bartholomew wrote:

> Interval>>includes: inherits from Collection which gives it a rather
> sub-optimal performance - it iterates through the complete range looking for
> the target. The following works a bit faster and provides, I think, the same
> results.
>
> includes: aNumber
>     ^aNumber >= (self first min: self last)
>             and: [aNumber <= (self first max: self last)]
>
> Regards
>     Ian
>
>
>
>
>
>
>


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

Ian Bartholomew
Eric,

> Hmmm....what about:

A very expressive Hmmm, if I may say so :)

Yes, I had a bit of tunnel vision there. My, very slow, app was using
Integers with a step of 1. I thought about different step directions but not
the obvious problem of different step values.  <sigh> It's been a long day
....

I'll just have to add a specialised version of #includes: for the
restricted, Integer only, case.

Thanks
    Ian


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

Don Rylander-3
Ian,

How about something like:

includes: aNumber
 |min max|
 min := start min: stop.
 max := stop max: start.
 ^(aNumber between: min and: max) and: [
  (aNumber - min \\ step) isZero]


Don

P.S. I needed to engage in some work avoidance.


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

Eric Winger-4
In reply to this post by Ian Bartholomew
Ian,

I haven't hashed this out fully, but this might work as a more general
includes: for Interval

includes: aNumber
        (aNumber isKindOf: Number) ifFalse:[^false].
     ^aNumber >= (self first min: self last)
             and: [aNumber <= (self first max: self last) and:[
                aNumber - self first \\ step = 0]]


Eric

Ian Bartholomew wrote:

> Eric,
>
>
>>Hmmm....what about:
>>
>
> A very expressive Hmmm, if I may say so :)
>
> Yes, I had a bit of tunnel vision there. My, very slow, app was using
> Integers with a step of 1. I thought about different step directions but not
> the obvious problem of different step values.  <sigh> It's been a long day
> ....
>
> I'll just have to add a specialised version of #includes: for the
> restricted, Integer only, case.
>
> Thanks
>     Ian
>
>
>
>
>


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

Ian Bartholomew
Eric/Don,

Thanks for the, very similar, suggestions. The only problem I noticed was
that floats might fail because of precision loss ...

(1.2 to: 99.3 by: 0.15) includes: 2.1

incorrectly answers false. One way round that could be to make the final
test use #equals: rather than #= or #isZero. You also than have to implement
#equals: in Number as well, to cope with Integers and Fractions, but that's
no problem.

As my original app always used Integers limits and a step of 1 I'll probably
go with a separate method, but overriding #includes: could be a change that
OA might consider for the image?

Regards
    Ian


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

Chris Uppal-3
Ian,

> As my original app always used Integers limits and a step of 1 I'll
probably
> go with a separate method, but overriding #includes: could be a change
that
> OA might consider for the image?

Or even the simple optimisation:

    ^ step = 1
            ifTrue: [...]
            ifFalse: [...].

could be worthwhile.  There can't be a *lot* of Intervals out there with
non-default step values.

    -- chris


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

Blair McGlashan
"Chris Uppal" <[hidden email]> wrote in message
news:[hidden email]...

> Ian,
>
> > As my original app always used Integers limits and a step of 1 I'll
> probably
> > go with a separate method, but overriding #includes: could be a change
> that
> > OA might consider for the image?
>
> Or even the simple optimisation:
>
>     ^ step = 1
>             ifTrue: [...]
>             ifFalse: [...].
>
> could be worthwhile.  There can't be a *lot* of Intervals out there with
> non-default step values.

I think this simple approach may well be the best. We'll adopt the consensus
though.

Regards

Blair


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

Ian Bartholomew
> I think this simple approach may well be the best. We'll adopt the
> consensus though.

As I started all this :) may I propose something like -

Interval>>includes: aNumber
    | first last |
    first := self first.
    last := self last.
    ^step = 1
        ifTrue: [aNumber >= first and: [aNumber <= last]]
        ifFalse:
            [aNumber >= (first min: last)
                and: [aNumber <= (first max: last)
                    and: [((aNumber - first) \\ step) asFloat equals: 0.0]]]

Comments?

Ian


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

Don Rylander-3
Ian,
"Ian Bartholomew" <[hidden email]> wrote in message
news:B2rd8.208$ZO1.22748@wards...
> > I think this simple approach may well be the best. We'll adopt the
> > consensus though.
>
> As I started all this :) may I propose something like -
>
> Interval>>includes: aNumber
>     | first last |
>     first := self first.
>     last := self last.
One (minor) surprise for me was that Interval doesn't always have the smallest
number as its first, e.g.:

    (99 to: 1 by: -2) first

evaluates to 99.

>     ^step = 1
>         ifTrue: [aNumber >= first and: [aNumber <= last]]
>         ifFalse:
>             [aNumber >= (first min: last)
>                 and: [aNumber <= (first max: last)
>                     and: [((aNumber - first) \\ step) asFloat equals: 0.0]]]
>
> Comments?

Don

>
> Ian
>
>
>
>


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

John Brant
In reply to this post by Ian Bartholomew
"Ian Bartholomew" <[hidden email]> wrote in message
news:B2rd8.208$ZO1.22748@wards...

> > I think this simple approach may well be the best. We'll adopt the
> > consensus though.
>
> As I started all this :) may I propose something like -
>
> Interval>>includes: aNumber
>     | first last |
>     first := self first.
>     last := self last.
>     ^step = 1
>         ifTrue: [aNumber >= first and: [aNumber <= last]]
>         ifFalse:
>             [aNumber >= (first min: last)
>                 and: [aNumber <= (first max: last)
>                     and: [((aNumber - first) \\ step) asFloat equals:
0.0]]]
>
> Comments?

Here's some tests you may want to use:

1) An empty interval:
(1 to: 0) includes: 1 ==> Index 1 is out of bounds error

2) Floats in integer intervals:
(1 to: 2) includes: 1.5 ==> true

3) Non-numbers:
(1 to: 2) includes: 'a' ==> Invalid arg 2: Cannot coerce a SmallInteger to a
lpstr error

All of these should return false.


John Brant


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

Ian Bartholomew
John, Don,

<FX> Sound of white flag waving</FX>

OK, I give in ;-)

> 1) An empty interval:
> (1 to: 0) includes: 1 ==> Index 1 is out of bounds error

That was actually deliberate. I called the #first and #last methods to
utilise the check it does for an empty collection, and cached it to prevent
multiple tests. If this behaviour is unwanted (which on further reflection
is probably the case) then going back to accessing the start and stop
instVars directly solves that.

> 2) Floats in integer intervals:

Yuk.

> 3) Non-numbers:

Perhaps it should raise a walkback anyway?.  I was surprised that ByteArray
doesn't either.

I hadn't really given in, and I came up with

includes: aNumber
    aNumber understandsArithmetic ifFalse: [^false].
    ^(step = 1 and: [aNumber isKindOf: Integer])
        ifTrue: [aNumber >= start and: [aNumber <= stop]]
        ifFalse:
            [aNumber >= (start min: stop)
                and: [aNumber <= (start max: stop)
                    and: [((aNumber - start) \\ step) asFloat equals: 0.0]]]

and then I tested it with

(-11 to: -55 by: 11) includes: -33

and decided that I might be better to give up after all!

Ian


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

Don Rylander-3
Ian,
"Ian Bartholomew" <[hidden email]> wrote in message
news:mpvd8.323$PE2.32729@stones...
> John, Don,
>
> <FX> Sound of white flag waving</FX>
>
> OK, I give in ;-)
Maybe it is time just to get on with our lives ;-)

> (-11 to: -55 by: 11) includes: -33
I think, though, your solution works.  You're bumping into the directional
problem I had earlier.  Look at the different results of these:

   (-11 to: -55 by: 11) collect: [:e|e] "It's empty, so -33 really isn't
included!"

   (-11 to: -55 by: -11) collect: [:e|e]

and I think you'll see what I mean.

Don

>
> and decided that I might be better to give up after all!
>
> Ian
>
>
>
>
>
>
>
>
>
>
>
>
>


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

Ian Bartholomew
Don,

> Maybe it is time just to get on with our lives ;-)

It's starting to get annoying though ...

>    (-11 to: -55 by: 11) collect: [:e|e] "It's empty, so -33 really isn't
> included!"

agreed, but the code in my last post answers true to the following
expression, so it's not correct.

(-11 to: -55 by: 11) includes: -33

Take 4 test cases

(11 to: 55 by: 11) includes: 33
(55 to: 11 by: 11) includes: 33
(11 to: 55 by: -11) includes: 33
(55 to: 11 by: -11) includes: 33

The correct answers, logically and using the existing code, are

true false false true

but my previous code gives

true true true true

It seems that you need to take the signs into account as well as the min and
max values so I came up with the following that seems to work both for the
above and the -ve equivalent as well.

includes: aNumber
    aNumber understandsArithmetic ifFalse: [^false].
    ^(step = 1 and: [aNumber isKindOf: Integer])
        ifTrue: [aNumber >= start and: [aNumber <= stop]]
        ifFalse:
            [| ans |
                ans := aNumber >= (start min: stop)
                    and: [aNumber <= (start max: stop)
                        and: [((aNumber - start) \\ step) asFloat equals:
0.0]].
            (stop - start) sign = step sign ifFalse: [ans := ans not].
            ans]

Ian

PS. I've just twigged that Chris and Blair may have meant something like the
following, a lot simpler :-)

    ^step = 1
        ifTrue: [aNumber >= start and: [aNumber <= stop]]
        ifFalse: [super includes: aNumber]


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

Blair McGlashan
In reply to this post by Don Rylander-3
"Don Rylander" <[hidden email]> wrote in
message news:a55ito$4r9hj$[hidden email]...
>...
> One (minor) surprise for me was that Interval doesn't always have the
smallest
> number as its first, e.g.:
>
>     (99 to: 1 by: -2) first
>
> evaluates to 99.

Which is correct. Interval is perhaps badly named in that it doesn't
represent an "interval", but an arithmetic "sequence". The sequence from 99
to 1 by -2 does indeed start at 99.

Regards

Blair


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

Eliot Miranda
In reply to this post by Ian Bartholomew
Ian Bartholomew wrote:
>
> Eric/Don,
>
> Thanks for the, very similar, suggestions. The only problem I noticed was
> that floats might fail because of precision loss ...
>
> (1.2 to: 99.3 by: 0.15) includes: 2.1
>
> incorrectly answers false.

which is why in VisualWorks Interval>>#do: is defined as
    do: aBlock
        "Evaluate aBlock with each of the receiver's elements as the argument."
        "We avoid accumulating a delta to minimize round-off error."

        | n end |

        "We don't use Number>>to:do: here because that would create a
        circularity."
        n := 0.
        end := self size - 1.
        [n <= end]
                whileTrue:
                        [aBlock value: start + (step * n).
                        n := n + 1]

So I suggest
    Interval>>#includes: anElement
        "Override for performance."

        ^anElement respondsToArithmetic
          and: [(step >= 0
                    ifTrue: [anElement >= start and: [anElement <= stop]]
                    ifFalse: [anElement >= stop and: [anElement <= start]])
          and: [(anElement - start \\ step) isZero]]

        "((-10 to: 10 by: 0.25) includes: 0.24) = ((-10 to: 10 by: 0.25)
asArray includes: 0.24)"
        "((-10 to: 10 by: 0.25) includes: 0.25) = ((-10 to: 10 by: 0.25)
asArray includes: 0.25)"
        "((-10 to: 10 by: 0.25) includes: 0.26) = ((-10 to: 10 by: 0.25)
asArray includes: 0.26)"
        "((-10 to: 10 by: 0.25) includes: 0@0) = ((-10 to: 10 by: 0.25) asArray
includes: 0@0)"
        "((0 to: 100 by: 0.333333) includes: 75.3333) = ((0 to: 100 by:
0.333333) asArray includes: 75.3333)"
        "((1 to: 0) includes: 1) = ((1 to: 0) asArray includes: 1)"
        "((1 to: 2) includes: 1.5) = ((1 to: 2) asArray includes: 1.5)"
        "((1 to: 2) includes: 'a') = ((1 to: 2) asArray includes: 'a')"
        "| interval |
         interval := 0 to: 100 by: (1/3) asFloat.
         interval reject: [:n| interval includes: n]"
        "| interval |
         interval := 0 to: -100 by: (1/3) asFloat negated.
         interval reject: [:n| interval includes: n]"


and to those that are suggesting we go back to our lives, if they could
only find me one...
--
_______________,,,^..^,,,____________________________
Eliot Miranda              Smalltalk - Scene not herd


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

Blair McGlashan
"Eliot Miranda" <[hidden email]> wrote in message
news:[hidden email]...
> ...
> which is why in VisualWorks Interval>>#do: is defined as
>     do: aBlock
> "Evaluate aBlock with each of the receiver's elements as the argument."
> "We avoid accumulating a delta to minimize round-off error."
> ...

Essentially the same is true in Dolphin (although the override is of
#from:to:keysAndValuesDo: which is the main override point for sequenceable
collections in Dolphin).

>
> So I suggest
>     Interval>>#includes: anElement
> "Override for performance."
>
> ^anElement respondsToArithmetic        "BSM: understandsArithmetic in
Dolphin"
>   and: [(step >= 0
>     ifTrue: [anElement >= start and: [anElement <= stop]]
>     ifFalse: [anElement >= stop and: [anElement <= start]])
>   and: [(anElement - start \\ step) isZero]]
> ...

Not bad, but it fails for:

>...
> "| interval |
> interval := 0 to: 100 by: (1/3) asFloat.
> interval reject: [:n| interval includes: n]"
> "| interval |
> interval := 0 to: -100 by: (1/3) asFloat negated.
> interval reject: [:n| interval includes: n]"

The results of the #reject:'s are supposed to be empty, and they are with
the inherited implementation., but representation error still gets you, for
example:

    (((0 + ((1/3) asFloat * (8-1))) - 0) \\ (1/3) asFloat) isZero    ==> is
false

at least on this AMD machine anyway.

Whether this is really an issue, is a bit of a moot point, since the
inherited implementation will also fail for flonums quite often when the
calculated value doesn't precisely match. For example:

    (0.01 to: 0.2 by: 0.01) includes: 0.1

This test fails with the inherited implementation too.

Regards

Blair


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

David Simmons-2
In reply to this post by Blair McGlashan
"Blair McGlashan" <[hidden email]> wrote in message
news:a55492$4ndgi$[hidden email]...

> "Chris Uppal" <[hidden email]> wrote in message
> news:[hidden email]...
> > Ian,
> >
> > > As my original app always used Integers limits and a step of 1 I'll
> > probably
> > > go with a separate method, but overriding #includes: could be a change
> > that
> > > OA might consider for the image?
> >
> > Or even the simple optimisation:
> >
> >     ^ step = 1
> >             ifTrue: [...]
> >             ifFalse: [...].
> >
> > could be worthwhile.  There can't be a *lot* of Intervals out there with
> > non-default step values.
>
> I think this simple approach may well be the best. We'll adopt the
consensus
> though.

Here is the interval #includes: implementation from the latest build of
SmallScript.

    Method behavior: Interval [
    includes: aValue
        ((aValue >= lowerBound and: [aValue <= upperBound])
            or: [aValue <= lowerBound and: [aValue >= upperBound]])
                ifFalse: [^false].
       ^(((aValue-lowerBound // step) * step)+lowerBound) = aValue
    ]

-- Dave S. [www.smallscript.org]

>
> Regards
>
> Blair
>
>


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

David Simmons-2
Which, now that I am looking it over, can be written slightly more tightly
as:

    Method behavior: Interval [
    includes: value
       ^((value >= lowerBound and: [value <= upperBound])
            or: [value <= lowerBound and: [value >= upperBound]])
                ifTrue: [(((value-lowerBound // step) * step)+lowerBound) =
value]
    ]

-- Dave S. [www.smallscript.org]

"David Simmons" <[hidden email]> wrote in message
news:[hidden email]...

>
> "Blair McGlashan" <[hidden email]> wrote in message
> news:a55492$4ndgi$[hidden email]...
> > "Chris Uppal" <[hidden email]> wrote in message
> > news:[hidden email]...
> > > Ian,
> > >
> > > > As my original app always used Integers limits and a step of 1 I'll
> > > probably
> > > > go with a separate method, but overriding #includes: could be a
change

> > > that
> > > > OA might consider for the image?
> > >
> > > Or even the simple optimisation:
> > >
> > >     ^ step = 1
> > >             ifTrue: [...]
> > >             ifFalse: [...].
> > >
> > > could be worthwhile.  There can't be a *lot* of Intervals out there
with

> > > non-default step values.
> >
> > I think this simple approach may well be the best. We'll adopt the
> consensus
> > though.
>
> Here is the interval #includes: implementation from the latest build of
> SmallScript.
>
>     Method behavior: Interval [
>     includes: aValue
>         ((aValue >= lowerBound and: [aValue <= upperBound])
>             or: [aValue <= lowerBound and: [aValue >= upperBound]])
>                 ifFalse: [^false].
>        ^(((aValue-lowerBound // step) * step)+lowerBound) = aValue
>     ]
>
> -- Dave S. [www.smallscript.org]
>
> >
> > Regards
> >
> > Blair
> >
> >
>
>


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

David Simmons-2
In reply to this post by Eliot Miranda
Ah, Yes. I like your solution better Eliot.

So I've modified the SmallScript one to:

    Method behavior: Interval [includes: v ^false]
    Method behavior: Interval [
    includes: <Number> aValue
       ^((value >= lowerBound and: [value <= upperBound])
            or: [value <= lowerBound and: [value >= upperBound]])
                ifTrue: [(value-lowerBound % step) = 0]
    ]

-- Dave S. [www.smallscript.org]

"Eliot Miranda" <[hidden email]> wrote in message
news:[hidden email]...
>
>
> Ian Bartholomew wrote:
> >
> > Eric/Don,
> >
> > Thanks for the, very similar, suggestions. The only problem I noticed
was

> > that floats might fail because of precision loss ...
> >
> > (1.2 to: 99.3 by: 0.15) includes: 2.1
> >
> > incorrectly answers false.
>
> which is why in VisualWorks Interval>>#do: is defined as
>     do: aBlock
> "Evaluate aBlock with each of the receiver's elements as the argument."
> "We avoid accumulating a delta to minimize round-off error."
>
> | n end |
>
> "We don't use Number>>to:do: here because that would create a
> circularity."
> n := 0.
> end := self size - 1.
> [n <= end]
> whileTrue:
> [aBlock value: start + (step * n).
> n := n + 1]
>
> So I suggest
>     Interval>>#includes: anElement
> "Override for performance."
>
> ^anElement respondsToArithmetic
>   and: [(step >= 0
>     ifTrue: [anElement >= start and: [anElement <= stop]]
>     ifFalse: [anElement >= stop and: [anElement <= start]])
>   and: [(anElement - start \\ step) isZero]]
>
> "((-10 to: 10 by: 0.25) includes: 0.24) = ((-10 to: 10 by: 0.25)
> asArray includes: 0.24)"
> "((-10 to: 10 by: 0.25) includes: 0.25) = ((-10 to: 10 by: 0.25)
> asArray includes: 0.25)"
> "((-10 to: 10 by: 0.25) includes: 0.26) = ((-10 to: 10 by: 0.25)
> asArray includes: 0.26)"
> "((-10 to: 10 by: 0.25) includes: 0@0) = ((-10 to: 10 by: 0.25) asArray
> includes: 0@0)"
> "((0 to: 100 by: 0.333333) includes: 75.3333) = ((0 to: 100 by:
> 0.333333) asArray includes: 75.3333)"
> "((1 to: 0) includes: 1) = ((1 to: 0) asArray includes: 1)"
> "((1 to: 2) includes: 1.5) = ((1 to: 2) asArray includes: 1.5)"
> "((1 to: 2) includes: 'a') = ((1 to: 2) asArray includes: 'a')"
> "| interval |
> interval := 0 to: 100 by: (1/3) asFloat.
> interval reject: [:n| interval includes: n]"
> "| interval |
> interval := 0 to: -100 by: (1/3) asFloat negated.
> interval reject: [:n| interval includes: n]"
>
>
> and to those that are suggesting we go back to our lives, if they could
> only find me one...
> --
> _______________,,,^..^,,,____________________________
> Eliot Miranda              Smalltalk - Scene not herd


12