Interval>>includes:

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

Re: Interval>>includes:

Keith Alcock-2
David,

Here is my 2-cent contribution to SmallScript.

I try to always use the a<b and b<c form when testing whether b is between a and c.  So, I
would write the condition as follows:

(lowerBound <= value and: [value <= upperBound])
   or: [upperBound <= value and: [value <= lowerBound]])

Then it is more obvious to me that the difference in the two cases is the transposition of
the bounds.  This implies, though, that the variable names are misleading, as you probably
noticed.

Also, your compiler might be able to optimize this version of the next test better and I
think it is more understandable.

[((value-lowerBound // step) * step) = (value-lowerBound)]

Thanks.


Keith Alcock




David Simmons wrote:

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


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

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

> ...
> 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 that fails some SUnit tests that assembled from various individuals
postings here:
1)    self deny: ((1 to: 0) includes: 1)        "assertion failure"

2)    self deny: ((1 to: 2) includes: 'a').        "type error in String>="

3)     interval := 0 to: 100 by: (1/3) asFloat. self assert: (interval
reject: [:n| interval includes: n]) isEmpty.

at least it does if I transpose this implementation into Dolphin, which I
might not have done correctly - I've pasted my transposition below.

Regards

Blair

----------------------

!Interval methodsFor!

includes: aValue
 ((aValue >= start and: [aValue <= stop])
  or: [aValue <= start and: [aValue >= stop]]) ifFalse: [^false].
 ^(aValue - start) // step * step + start = aValue! !
!Interval categoriesFor: #includes:!public!searching! !


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

Ian Bartholomew
In reply to this post by David Simmons-2
"David Simmons" <[hidden email]> wrote in message
news:[hidden email]...

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

Doesn't that still fail with the case mentioned in the other part of the
thread, where the collection direction differs from the step direction. For
example -

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

Ian


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

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

> 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, what does #ifTrue: evaluate to in Smallscript if the condition is
false? Traditionally in Smalltalk the value of the unspecified branch is
nil, so this wouldn't work?

Regards

Blair


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

Chris Uppal-3
In reply to this post by Ian Bartholomew
Ian, John, Don,

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

Another nasty case is:

    (1.5 to: 3.5) includes: 3.5.

which makes my "simple optimisation" less useful than I'd thought.

Also non-normalised fractions, and big numbers that won't coerce to Floats
cause problems, two examples in one:

    big := 400 factorial.
    frac := Fraction numerator: big+1 denominator: 1.
    (big to: big + 2) includes: frac.

It's possible to code for this (obviously) but it's getting very messy.  I
haven't yet noticed anything that breaks the following (but I'm sure someone
else will).  Sorry about the line wrapping.
------------------
Interval>>includes2: target
    "Answer whether the <Object> argument, target, is one of the elements of
    the receiver.
    Implementation Note: complicated arithmetic tests to avoid looping over
    the virtual collection."

    | from to div |

    target understandsArithmetic ifFalse: [^ false].
    step > 0
        ifTrue: [from := start. to := stop]
        ifFalse: [from := stop. to := start].

    target < from ifTrue: [^ false].
    target > to ifTrue: [^ false].

    "ugly but useful special case, most Intervals have step == 1
    (note the implicit test that step isKindOf: Integer)"
    (step == 1 and: [(from isKindOf: Integer) and: [target isKindOf:
Integer]]) ifTrue: [^ true].

    div := target - from / step.
    ^ div = div truncated. "i.e. div is a whole number in whatever
representation"
------------------

BTW, some timings:

(1 to: 10) includes: -1.        "15.3 (+/-0.3) microseconds"
(1 to: 10) includes: 1.         "6.6 (+/-0.2) microseconds"
(1 to: 10) includes: 10.       "14.5 (+/-0.3) microseconds"
(1 to: 1000000) includes: 1000000.
                                                "855 (+/-2) milliseconds"

(1 to: 10) includes2: -1.      "2.5 (+/-0.1) microseconds"
(1 to: 10) includes2: 1.       "3.2 (+/-0.1) microseconds"
(1 to: 10) includes2: 10.    "3.1 (+/-0.2) microseconds"
(1 to: 1000000) includes2: 1000000.
                                                "3.1 (+/-0.1) microseconds"


    -- chris


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

John Brant
"Chris Uppal" <[hidden email]> wrote in message
news:[hidden email]...

> Ian, John, Don,
>
> > and decided that I might be better to give up after all!
>
> Another nasty case is:
>
>     (1.5 to: 3.5) includes: 3.5.
>
> which makes my "simple optimisation" less useful than I'd thought.
>
> Also non-normalised fractions, and big numbers that won't coerce to Floats
> cause problems, two examples in one:
>
>     big := 400 factorial.
>     frac := Fraction numerator: big+1 denominator: 1.
>     (big to: big + 2) includes: frac.
>
> It's possible to code for this (obviously) but it's getting very messy.  I
> haven't yet noticed anything that breaks the following (but I'm sure
someone
> else will).  Sorry about the line wrapping.
> ------------------
> Interval>>includes2: target
>     "Answer whether the <Object> argument, target, is one of the elements
of
>     the receiver.
>     Implementation Note: complicated arithmetic tests to avoid looping
over

>     the virtual collection."
>
>     | from to div |
>
>     target understandsArithmetic ifFalse: [^ false].
>     step > 0
>         ifTrue: [from := start. to := stop]
>         ifFalse: [from := stop. to := start].
>
>     target < from ifTrue: [^ false].
>     target > to ifTrue: [^ false].
>
>     "ugly but useful special case, most Intervals have step == 1
>     (note the implicit test that step isKindOf: Integer)"
>     (step == 1 and: [(from isKindOf: Integer) and: [target isKindOf:
> Integer]]) ifTrue: [^ true].
>
>     div := target - from / step.
>     ^ div = div truncated. "i.e. div is a whole number in whatever
> representation"
> ------------------

But this one doesn't work for the (1/3) asFloat case that Blair has posted.
Here's my code that works for the Blair's test case:

includes: aNumber
     aNumber understandsArithmetic ifFalse: [^false].
     self isEmpty ifTrue: [^false].
     (aNumber between: (start min: stop) and: (start max: stop))
          ifFalse: [^false].
     ^step isInteger
          ifTrue: [(aNumber - start) \\ step = 0]
          ifFalse: [start + (step * ((aNumber - start) / step) rounded) =
aNumber] "We could always use this line, but I'd prefer not to create a
fraction."

Now, what test cases am I missing?


John Brant


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

Ian Bartholomew
John,

> Now, what test cases am I missing?

How about Float imprecision, as in -

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

You can get around this by using #equals: in the last line, but you would
also need to implement it in Number to allow other numeric classes to work.

start + (step * ((aNumber - start) / step) rounded) equals: aNumber

I like the #isEmpty test though, it avoids a number of pitfalls.

Ian


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

John Brant
"Ian Bartholomew" <[hidden email]> wrote in message
news:a58jd3$5huuo$[hidden email]...

> > Now, what test cases am I missing?
>
> How about Float imprecision, as in -
>
> (1.2 to: 3.0 by: 0.15) includes: 2.1

But, "(1.2 to: 3.0 by: 0.15)" doesn't include 2.1 :). Try it with the
original #includes:, or you can use: "(1.2 to: 3.0 by: 0.15) asArray
includes: 2.1". The #includes: message should only return true for those
objects that are enumerated by #do:. BTW, if you inspect the floats, you'll
see the difference between the 2.1 you enter in code and the 2.1 in the
interval -- the first byte is 205 in the code and 204 in the interval.


John Brant


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

Ian Bartholomew
"John Brant" <[hidden email]> wrote in message
news:AWQd8.15752$%[hidden email]...

> But, "(1.2 to: 3.0 by: 0.15)" doesn't include 2.1 :). Try it with the
> original #includes:, or you can use: "(1.2 to: 3.0 by: 0.15) asArray
> includes: 2.1".

Yes it does.

(1.2 to: 3.0 by: 0.15) asArray anySatisfy: [:each | each equals: 2.1]
... answers true

Just joking :-). I can see what you are saying and the reasoning behind it,
Interval is a Collection class and should behave as other Collection classes
when enumerating over Float values. I'm not sure I agree with it, if you can
get full accuracy when using an Interval then why not take advantage of it,
but can accept it as one of the pitfalls to be aware of when using Floats.

Regards
    Ian


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

David Simmons-2
In reply to this post by Keith Alcock-2
"Keith Alcock" <[hidden email]> wrote in message
news:[hidden email]...
> David,
>
> Here is my 2-cent contribution to SmallScript.
>
> I try to always use the a<b and b<c form when testing whether b is between
a and c.  So, I
> would write the condition as follows:
>
> (lowerBound <= value and: [value <= upperBound])
>    or: [upperBound <= value and: [value <= lowerBound]])
>
> Then it is more obvious to me that the difference in the two cases is the
transposition of
> the bounds.  This implies, though, that the variable names are misleading,
as you probably
> noticed.
>
> Also, your compiler might be able to optimize this version of the next
test better and I
> think it is more understandable.
>
> [((value-lowerBound // step) * step) = (value-lowerBound)]
>
> Thanks.

Thanks Keith. In general, I agree with the principle behind the "a<b" and
"b<c" form. But I'm not comfortable with any of the possible forms. For
example, here I think it implies writing something like:

    value >= start and: [value <= end]
        or: [value >= end and: [value <= start]]]

FYI. The following is what the current implementation looks like:

    Method [
    includes: <Number> value
        |normalized := value - lowerBound|
       ^((normalized >= 0 and: [value <= upperBound])
            or: [normalized <= 0 and: [value >= upperBound]])
                ifTrue: [(normalized // step * step) = normalized]
    ]

Noting that a "isZero" test will not work depending on sign and truncation
rules for integral division.

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

>
>
> Keith Alcock
>
>
>
>
> David Simmons wrote:
> >
> > 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]
> >


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:a57tp4$592b0$[hidden email]...

> "David Simmons" <[hidden email]> wrote in message
> news:[hidden email]...
> > ...
> > 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 that fails some SUnit tests that assembled from various individuals
> postings here:
> 1)    self deny: ((1 to: 0) includes: 1)        "assertion failure"
>
> 2)    self deny: ((1 to: 2) includes: 'a').        "type error in
String>="
>
> 3)     interval := 0 to: 100 by: (1/3) asFloat. self assert: (interval
> reject: [:n| interval includes: n]) isEmpty.
>
> at least it does if I transpose this implementation into Dolphin, which I
> might not have done correctly - I've pasted my transposition below.

Sorry. I did not include the multi-method <Number> qualifier in that post.

    Method [includes: value ^false]
    Method [includes: <Number> value ...]

Without multi-methods you need to write something like:

    Method [
    includes: value
        ^(value isKindOf: Number) ifTrue [
            ...
        ]
    ]

Or, if you have a #implementsNumerics method then you can use that instead
of #isKindOf:.

P.S., this is the current implementation:

    Method [
    includes: <Number> value
        |normalized := value - lowerBound|
       ^((normalized >= 0 and: [value <= upperBound])
            or: [normalized <= 0 and: [value >= upperBound]])
                ifTrue: [(normalized // step * step) = normalized]
    ]

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

>
> Regards
>
> Blair
>
> ----------------------
>
> !Interval methodsFor!
>
> includes: aValue
>  ((aValue >= start and: [aValue <= stop])
>   or: [aValue <= start and: [aValue >= stop]]) ifFalse: [^false].
>  ^(aValue - start) // step * step + start = aValue! !
> !Interval categoriesFor: #includes:!public!searching! !
>
>
>
>
>


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:a57u2k$59p02$[hidden email]...

> "David Simmons" <[hidden email]> wrote in message
> news:[hidden email]...
> > 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, what does #ifTrue: evaluate to in Smallscript if the condition is
> false? Traditionally in Smalltalk the value of the unspecified branch is
> nil, so this wouldn't work?

By definition (in SmallScript), a conditional test returns the tested value
as the "value" of a missing/implied branch clause. And, it also provides the
"test" value as an implicit argument into a branch clause.

    "" This is the implicit form
    someExpr
        ifTrue: [:someExpr| someExpr]
        ifFalse: [:someExpr| someExpr]

    someExpr
        ifZero: [:someExpr| someExpr]
        ifNotZero: [:someExpr| someExpr]


    someExpr
        ifNil: [:someExpr| someExpr]
        ifNotNil: [:someExpr| someExpr]

etc.

So, if we write:

    |r| := someExpr ifTrue: [...].

And <someExpr> evaluates to "false", then <r> will be set to <someExpr>.

<SIDENOTE>
SmallScript supports var-args (&rest) args in blocks and within methods. So
the number of arguments a block is "valued" with does not have to be the
same as the number it was "declared" with.

The following is perfectly valid (and will work as expected for <v>).

    |b0| := [stdout cr << 'we do not care'].
    |b1| := [:v| stdout cr << v].

    true ifTrue: b0.
    'blah' ifNotNil: b0.

    true ifTrue: b1.
    'blah' ifNotNil: b1.

    true ifTrue: b1 ifFalse: b0.
    'blah' ifNotNil: b1 ifNil: b0.

    true ifTrue: b0 ifFalse: b1.
    'blah' ifNotNil: b0 ifNil: b1.
</SIDENOTE>

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

>
> Regards
>
> Blair
>
>


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

Chris Uppal-3
In reply to this post by John Brant
John,

> But this one doesn't work for the (1/3) asFloat case that Blair has
posted.

I hadn't recieved Blair's post at the time.  Yes you are right.  Anyway it
has another bug: I was testing "from isKindOf: Integer" instead of "start
isKindOf: Integer".

Suprisingly tricky...

> Here's my code that works for the Blair's test case:
>
> includes: aNumber
>      aNumber understandsArithmetic ifFalse: [^false].
>      self isEmpty ifTrue: [^false].
>      (aNumber between: (start min: stop) and: (start max: stop))
>           ifFalse: [^false].
>      ^step isInteger
>           ifTrue: [(aNumber - start) \\ step = 0]
>           ifFalse: [start + (step * ((aNumber - start) / step) rounded) =
> aNumber] "We could always use this line, but I'd prefer not to create a
> fraction."
>
> Now, what test cases am I missing?

I can't think of any.  The important thing is that your last line follows
the form of the arithmetic underlying Interval>>do:.

I suspect it might be possible to break it by using large start and stop
(BinIntegers) and a small (Fraction) step, and then taking aNumber to be
floating point.  But, even if that's true, that is just a problem with the
concept of mixing floating point with Interval, rather than a problem with
your implementation.

> John Brant

    -- chris


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

David Simmons-2
In reply to this post by David Simmons-2
Blair,

Here is a follow-on from discussion in the comp.lang.smallscript newsgroup.

    Class ref-name: Interval
    {
        Method [isEmpty ^(upperBound - lowerBound).sign !== step.sign]
        Method [
        includes: <Number> value
            |normalized := value - lowerBound|
           ^((normalized >= 0 and: [value <= upperBound])
                or: [normalized <= 0 and: [value >= upperBound]])
                    and: [(normalized // step * step) = normalized
                        and: [((upperBound - lowerBound).sign ==
step.sign)]]
        ]
    }

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

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

> "Blair McGlashan" <[hidden email]> wrote in message
> news:a57u2k$59p02$[hidden email]...
> > "David Simmons" <[hidden email]> wrote in message
> > news:[hidden email]...
> > > 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, what does #ifTrue: evaluate to in Smallscript if the condition is
> > false? Traditionally in Smalltalk the value of the unspecified branch is
> > nil, so this wouldn't work?
>
> By definition (in SmallScript), a conditional test returns the tested
value
> as the "value" of a missing/implied branch clause. And, it also provides
the

> "test" value as an implicit argument into a branch clause.
>
>     "" This is the implicit form
>     someExpr
>         ifTrue: [:someExpr| someExpr]
>         ifFalse: [:someExpr| someExpr]
>
>     someExpr
>         ifZero: [:someExpr| someExpr]
>         ifNotZero: [:someExpr| someExpr]
>
>
>     someExpr
>         ifNil: [:someExpr| someExpr]
>         ifNotNil: [:someExpr| someExpr]
>
> etc.
>
> So, if we write:
>
>     |r| := someExpr ifTrue: [...].
>
> And <someExpr> evaluates to "false", then <r> will be set to <someExpr>.
>
> <SIDENOTE>
> SmallScript supports var-args (&rest) args in blocks and within methods.
So

> the number of arguments a block is "valued" with does not have to be the
> same as the number it was "declared" with.
>
> The following is perfectly valid (and will work as expected for <v>).
>
>     |b0| := [stdout cr << 'we do not care'].
>     |b1| := [:v| stdout cr << v].
>
>     true ifTrue: b0.
>     'blah' ifNotNil: b0.
>
>     true ifTrue: b1.
>     'blah' ifNotNil: b1.
>
>     true ifTrue: b1 ifFalse: b0.
>     'blah' ifNotNil: b1 ifNil: b0.
>
>     true ifTrue: b0 ifFalse: b1.
>     'blah' ifNotNil: b0 ifNil: b1.
> </SIDENOTE>
>
> -- Dave S. [www.smallscript.org]
>
> >
> > Regards
> >
> > Blair
> >
> >
>
>


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

Blair McGlashan
In reply to this post by John Brant
"John Brant" <[hidden email]> wrote in message
news:TCOd8.123047$Pz4.543493@rwcrnsc53...
> ....
> But this one doesn't work for the (1/3) asFloat case that Blair has
posted.

> Here's my code that works for the Blair's test case:
>
> includes: aNumber
>      aNumber understandsArithmetic ifFalse: [^false].
>      self isEmpty ifTrue: [^false].
>      (aNumber between: (start min: stop) and: (start max: stop))
>           ifFalse: [^false].
>      ^step isInteger
>           ifTrue: [(aNumber - start) \\ step = 0]
>           ifFalse: [start + (step * ((aNumber - start) / step) rounded) =
> aNumber] "We could always use this line, but I'd prefer not to create a
> fraction."
>
> Now, what test cases am I missing?

That certainly passes all my tests. A small optimization is to combine the
#isEmpty test together with the following range test since to reduce the
number of comparisons, but it makes the code less clear.

------------------------
 anObject understandsArithmetic ifFalse: [^false].
 (step < 0
  ifTrue: [anObject >= stop and: [anObject <= start]]
  ifFalse: [anObject >= start and: [anObject <= stop]]) ifFalse: [^false].
 ^step isInteger
  ifTrue: [(anObject - start) \\ step = 0]
  ifFalse: [start + (step * ((anObject - start) / step) rounded) = anObject]
---------------------------

Regards

Blair


Reply | Threaded
Open this post in threaded view
|

Re: Interval>>includes:

Don Roberts
In reply to this post by Ian Bartholomew
Related to this discussion, I've needed a mathematical interval object
several times. The Smalltalk Interval is basically an arithmetic
sequence. I want a mathematical interval that is an uncountably infinite
set of floats that can be unioned, intersected, etc. These beasts crop up
quite a bit in graphics and error checking.

(Of course I could write one, but then I'd have to stop reading
newsgroups :) )

don


12