Re: [Haskell-cafe] Strange subtract operator behavior - and lazy naturals

2007-10-21 Thread Yitzchak Gale
I wrote:

Yitzchak Gale wrote:
>> So why not make the laziness available
>> also for cases where "1 - 2 == 0" does _not_ do
>> the right thing?
>> data LazyInteger = IntZero | IntSum Bool Integer LazyInteger
>> or
>> data LazyInteger = LazyInteger Bool Nat
>> or whatever.

Luke Palmer wrote:
> data LazyInteger = IntDiff Nat Nat
> The only value which would diverge when
> compared to a constant would be infinity - infinity.

Hmm. But then you could have integers that are
divergent and non-infinite. What do we gain by
doing it this way?

-Yitz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange subtract operator behavior - and lazy naturals

2007-10-20 Thread Luke Palmer
On 10/19/07, Yitzchak Gale <[EMAIL PROTECTED]> wrote:
> So why not make the laziness available
> also for cases where "1 - 2 == 0" does _not_ do
> the right thing?
>
> data LazyInteger = IntZero | IntSum Bool Integer LazyInteger
>
> or
>
> data LazyInteger = LazyInteger Bool Nat

I think

data LazyInteger = IntDiff Nat Nat

would admit implementation of most of the nice properties of this
implementation.  Comparison operators could short circuit when one of
the two naturals is zero.  The only  value which would diverge when
compared to a constant would be infinity - infinity.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange subtract operator behavior - and lazy naturals

2007-10-19 Thread Yitzchak Gale
Hi John,

I wrote:
>> - Zero really means 0, not "0 or negative"

You wrote:
> Actually, zero does mean zero. There is no such thing as negative
> numbers in the naturals so it doesn't make sense to say '0 or negative'.

Well, then, "0 or error", or "0 or nothing". It clearly
does not mean zero.

> Subtraction is necessarily defined differently of course.

As described in the referenced paper,
(yes, an enjoyable read, thanks) this is for
convenience only. No one is claiming that 1 - 2 == 0
in the naturals. It is just undefined. But we
find that returning Zero rather than raising
an exception happens to do the right thing for
certain common usages of the naturals.

Anyway, my point is that you have done two good
things here that are orthogonal to each other:
a good lazy integral type, and a good naturals type.

So why not make the laziness available
also for cases where "1 - 2 == 0" does _not_ do
the right thing?

data LazyInteger = IntZero | IntSum Bool Integer LazyInteger

or

data LazyInteger = LazyInteger Bool Nat

or whatever.

Thanks,
Yitz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange subtract operator behavior - and lazy naturals

2007-10-18 Thread John Meacham
On Thu, Oct 18, 2007 at 01:58:14PM +0200, Yitzchak Gale wrote:
> - Zero really means 0, not "0 or negative".

Actually, zero does mean zero. There is no such thing as negative
numbers in the naturals so it doesn't make sense to say '0 or negative'.

Subtraction is necessarily defined differently of course. As in, a
natural number type was actually my goal as it is the "natural" choice
for a lot of operations (hah! pun!), it wasn't a concession. 

I found the paper that originally inspired me to write this class:
http://citeseer.ist.psu.edu/45669.html

it is a good read.

John


-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange subtract operator behavior - and lazy naturals

2007-10-18 Thread Yitzchak Gale
I wrote:
>> Nice, lots of fun!
>> Wouldn't it be more convenient to allow them
>> to be signed?

John Meacham wrote:
> Well, a couple reasons. One is that Natural numbers are a pretty useful
> type in and of themselves, often times when used with lazy evaluation.
> The other is that it is unclear what semantics lazy signed numbers would
> have...

True. I was thinking of the sign at the beginning - which
means, essentially, the same as what you already have.
The real only differences are:

- Zero really means 0, not "0 or negative".
- In certain special cases where you happen to know that
  the result should be a certain negative number, you get that

In particular, the scrictness properties - which you have already
so carefully worked out for the case of the naturals -
do not change.

Of course, you can then easily restrict to the naturals
when you want that.

-Yitz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange subtract operator behavior - and lazy naturals

2007-10-17 Thread David Benbennick
On 10/17/07, John Meacham <[EMAIL PROTECTED]> wrote:
> Oops, sorry, the version I posted was an intermediate one that had a
> different addition algorithm. here is a better one that fixes that issue:
>
> Zero + y = y
> Sum x n1 + y = Sum x (y + n1)
>
> note that it alternates the order in the recursive call, interleaving
> the elements of the two arguments.

Thanks.

Have you thought at all about how to make "maximally lazy" Naturals?
For example, a data type that can answer True to both

genericLength (1:undefined) + genericLength (1:2:3:4:5:6:undefined) > (6 :: Nat)

genericLength (1:2:3:4:5:6:undefined) + genericLength (1:undefined) > (6 :: Nat)

Is that a desired feature?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange subtract operator behavior - and lazy naturals

2007-10-17 Thread John Meacham
On Wed, Oct 17, 2007 at 05:43:08PM -0700, David Benbennick wrote:
> This module doesn't appear to be very lazy to me.  For example, in ghci,
> 
> *Util.LazyNum List> genericLength (1:2:undefined) > (1 :: Nat)
> *** Exception: Prelude.undefined
> 
> How is this module intended to be used?

Oops, sorry, the version I posted was an intermediate one that had a
different addition algorithm. here is a better one that fixes that issue:

Zero + y = y
Sum x n1 + y = Sum x (y + n1)  

note that it alternates the order in the recursive call, interleaving
the elements of the two arguments.

so, this is head-strict in the left argument, but tail-lazy in both. 

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange subtract operator behavior - and lazy naturals

2007-10-17 Thread David Benbennick
This module doesn't appear to be very lazy to me.  For example, in ghci,

*Util.LazyNum List> genericLength (1:2:undefined) > (1 :: Nat)
*** Exception: Prelude.undefined

How is this module intended to be used?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange subtract operator behavior - and lazy naturals

2007-10-17 Thread John Meacham
On Wed, Oct 17, 2007 at 09:16:47PM +0100, Lennart Augustsson wrote:
> The one in the numbers package is not quite as clever as John's; it's the
> naïve version of lazy naturals.

it appears to also be left biased in general, mine are symmetric and
commutative whenever possible and things like its division arn't lazy
when they could be (since it computes the modulus at the same time). 

Another difference is that I use capping behavior at zero rather than
producing an error. This has a variety of nice algebraic properties (in
addition to not bottoming out). unfortunately I can't find the paper
that I read about them at the moment hmm...

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange subtract operator behavior - and lazy naturals

2007-10-17 Thread John Meacham
On Wed, Oct 17, 2007 at 12:41:54PM +0200, Yitzchak Gale wrote:
> John Meacham wrote:
> > if anyone is interested, Although I bet this has been implemented a
> > hundred times over, I have attached my lazy naturals module below just
> > for larks.
> 
> Nice, lots of fun!
> 
> Wouldn't it be more convenient to allow them
> to be signed? True, you can't have laziness in
> certain cases, and certain calculations would
> be non-convergent. But you already have
> things like that, e.g subtraction, and natEven.

Well, a couple reasons. One is that Natural numbers are a pretty useful
type in and of themselves, often times when used with lazy evaluation.
The other is that it is unclear what semantics lazy signed numbers would
have, if the sign were at the beginning, then addition and subtraction
would be strict, because you can't figure out the sign of the result
without running through to the end of the number. Another possibility
which would preserve full lazyness is
to just allow negative numbers in Sum. which has other issues, such as
you no longer have the property that

Sum x (Sum _ _) > Sum x Zero

so you couldn't short circuit comparison operations.

All in all, it wasn't clear what the correct tradeoffs would be and I
wanted numbers restricted to naturals as much as I wanted lazy numbers. 

> > Anyone have any comments on my lazy multiplication algorithm?
> 
> Looks fine to me. It introduces left-bias, but you have
> to do it one way or the other.

Yeah, It was fairly subtle, I tried various permutations of making it
strict or lazy and removing the bias. I can't say I fully understand why
this form is the best. something odd is that If I don't rebuild the
second argument (y + ry) but use the original second value placed in, it
drastically slows things down.

> > since (+) is lazy, we can still get a good lazy result without
> > evaluating the tails when multiplying... that is nice.
> 
> Yes.
> 
> > n `mod` 0 should be?
> 
> It's negative infinity if n > 0, but you don't
> allow negative numbers. I suppose it should
> be Zero - in your implementation, Zero does
> not exactly have the semantics of 0. Instead,
> it means "either 0 or negative".

yes. something like that, I read a paper somewhere that defined negative 



> > If anyone wants me to clean this up and package it as a real module, I
> > would be happy to do so.
> 
> Please at least post it to the wiki.

okay, I will clean it up some and add more documentation as to the
strictness. In general, I tried to make everything 'head-strict' in both
arguments, but symmetrically 'tail-lazy'. if that makes sense at all. I
need to come up with some better terminology.

also, div is tail-lazy, but mod is tail-strict.

I have found assymetric addition to be useful actually and will export
it as a separate function, where instead of 'zipping' the two lazy
numbers together, it appends the second to the first, making it fully
lazy in the second argument. It is mainly useful for tying the knot to
make infinite numbers, but can sometimes affect 

hmm.. is there any established terminology for this sort of thing? my
thought is something like:

lazy - fully lazy, _|_ and Infinity can be passed in.

tail-lazy - can produce results without traversing the whole number,
such as division, addition, and multiplication, Infinity can safely be passed 
in.

head-strict - you can't pass in _|_, but you may or may not be able to pass in
Infinity

fully strict - you can't pass in _|_ or Infinity and expect a result.
'mod' is an example. 

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange subtract operator behavior - and lazy naturals

2007-10-17 Thread Lennart Augustsson
The one in the numbers package is not quite as clever as John's; it's the
naïve version of lazy naturals.

On 10/17/07, Stuart Cook < [EMAIL PROTECTED]> wrote:
>
> On 10/17/07, John Meacham < [EMAIL PROTECTED]> wrote:
> > if anyone is interested, Although I bet this has been implemented a
> > hundred times over, I have attached my lazy naturals module below just
> > for larks. It is quite efficient as such things go and very lazy. for
> > instance (genericLength xs > 5) will only evaluate up to the 5th element
> > of the list before returning a result. and ((1 `div` 0) > 17) is true,
> > not bottom.
>
> > If anyone wants me to clean this up and package it as a real module, I
> > would be happy to do so.
>
> It looks like there's already a lazy-natural type in the "numbers"
> package on Hackage, but not having used it I have no idea what it's
> like.
>
>
> http://hackage.haskell.org/cgi-bin/hackage-scripts/package/numbers-2007.9.25
> http://tinyurl.com/2pmthz
>
>
> Stuart
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange subtract operator behavior - and lazy naturals

2007-10-17 Thread Stuart Cook
On 10/17/07, John Meacham <[EMAIL PROTECTED]> wrote:
> if anyone is interested, Although I bet this has been implemented a
> hundred times over, I have attached my lazy naturals module below just
> for larks. It is quite efficient as such things go and very lazy. for
> instance (genericLength xs > 5) will only evaluate up to the 5th element
> of the list before returning a result. and ((1 `div` 0) > 17) is true,
> not bottom.

> If anyone wants me to clean this up and package it as a real module, I
> would be happy to do so.

It looks like there's already a lazy-natural type in the "numbers"
package on Hackage, but not having used it I have no idea what it's
like.

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/numbers-2007.9.25
http://tinyurl.com/2pmthz


Stuart
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange subtract operator behavior - and lazy naturals

2007-10-17 Thread Yitzchak Gale
John Meacham wrote:
> if anyone is interested, Although I bet this has been implemented a
> hundred times over, I have attached my lazy naturals module below just
> for larks.

Nice, lots of fun!

Wouldn't it be more convenient to allow them
to be signed? True, you can't have laziness in
certain cases, and certain calculations would
be non-convergent. But you already have
things like that, e.g subtraction, and natEven.

> Anyone have any comments on my lazy multiplication algorithm?

Looks fine to me. It introduces left-bias, but you have
to do it one way or the other.

> since (+) is lazy, we can still get a good lazy result without
> evaluating the tails when multiplying... that is nice.

Yes.

> n `mod` 0 should be?

It's negative infinity if n > 0, but you don't
allow negative numbers. I suppose it should
be Zero - in your implementation, Zero does
not exactly have the semantics of 0. Instead,
it means "either 0 or negative".

> If anyone wants me to clean this up and package it as a real module, I
> would be happy to do so.

Please at least post it to the wiki.

> sorry for the tangent. just one of those days.

I know the feeling... :)

Thanks,
Yitz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange subtract operator behavior - and lazy naturals

2007-10-16 Thread John Meacham
On Wed, Oct 17, 2007 at 03:13:23AM +0100, Lennart Augustsson wrote:
> If naturals have a perfectly reasonable subtraction then they also have a
> perfectly reasonable negate; the default is 0-x.
> 
> (Oh, subtraction wasn't THAT reasonable, you say. :) )


I suppose I was overextending the use of 'perfectly reasonable' here. :)

tangent:

if anyone is interested, Although I bet this has been implemented a
hundred times over, I have attached my lazy naturals module below just
for larks. It is quite efficient as such things go and very lazy. for
instance (genericLength xs > 5) will only evaluate up to the 5th element
of the list before returning a result. and ((1 `div` 0) > 17) is true,
not bottom.

Anyone have any comments on my lazy multiplication algorithm? since each
number is of the form (x + rx) (an integer, plus the lazy remainder) I
just did the multiplicitive expansion 

(x + rx) * (y + ry) -> x*y + x*ry + y*rx + rx*ry
then I simplify to 
(x + rx) * (y + ry) -> x*y + x*ry + rx*(y + ry)
which saves a nice recursive call to * speeding thinsg up signifigantly.
but is there a better way?

since (+) is lazy, we can still get a good lazy result without
evaluating the tails when multiplying... that is nice.

also, what do you think 
n `mod` 0 should be? I can see arguments for it being 'n', 0, or
Infinity depending on how you look at it.. hmm..


If anyone wants me to clean this up and package it as a real module, I
would be happy to do so.

sorry for the tangent. just one of those days.

John


-- 
John Meacham - ⑆repetae.net⑆john⑈

-- Copyright (c) 2007 John Meacham (john at repetae dot net)
-- 
-- Permission is hereby granted, free of charge, to any person obtaining a
-- copy of this software and associated documentation files (the
-- "Software"), to deal in the Software without restriction, including
-- without limitation the rights to use, copy, modify, merge, publish,
-- distribute, sublicense, and/or sell copies of the Software, and to
-- permit persons to whom the Software is furnished to do so, subject to
-- the following conditions:
-- 
-- The above copyright notice and this permission notice shall be included
-- in all copies or substantial portions of the Software.
-- 
-- THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS
-- OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
-- MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT.
-- IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY
-- CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT,
-- TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE
-- SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.

-- efficient lazy naturals

module Util.LazyNum where

-- Nat data type is eqivalant to a type restricted lazy list that is strict in
-- its elements.
--
-- Invarients: (Sum x _) => x > 0
-- in particular (Sum 0 _) is _not_ valid and must not occur.

data Nat = Sum !Integer Nat | Zero
deriving(Show)

instance Eq Nat where
Zero == Zero = True
Zero == _ = False
_ == Zero = False
Sum x nx == Sum y ny = case compare x y of
EQ -> nx == ny
LT -> nx == Sum (y - x) ny
GT -> Sum (x - y) nx == ny


instance Ord Nat where
Zero <= _ = True
_ <= Zero = False
Sum x nx <= Sum y ny = case compare x y of
EQ -> nx <= ny
LT -> nx <= Sum (y - x) ny
GT -> Sum (x - y) nx <= ny

Zero `compare` Zero = EQ
Zero `compare` _ = LT
_`compare` Zero = GT
Sum x nx `compare` Sum y ny = case compare x y of
EQ -> nx `compare` ny
LT -> nx `compare` Sum (y - x) ny
GT -> Sum (x - y) nx `compare` ny

x < y = not (x >= y)
x >= y = y <= x
x > y = y < x


instance Num Nat where
Zero + y = y
x + Zero = x
Sum x n1 + Sum y n2 = Sum (x + y) (n1 + n2)

Zero - _ = zero
x - Zero = x
Sum x n1 - Sum y n2 = case compare x y of
GT -> Sum (x - y) n1 - n2
EQ -> n1 - n2
LT -> n1 - Sum (y - x) n2
negate _ = zero
abs x = x
signum Zero = zero
signum _ = one
fromInteger x = if x <= 0 then zero else Sum x Zero

Zero * _ = Zero
_ * Zero = Zero
(Sum x nx) * (Sum y ny) = Sum (x*y) ((f x ny) + (nx * (fint y + ny))) where
f y Zero = Zero
f y (Sum x n) = Sum (x*y) (f y n)



instance Real Nat where
toRational n = toRational (toInteger n)

instance Enum Nat where
succ x = Sum 1 x
pred Zero = Zero
pred (Sum n x) = if n == 1 then x else Sum (n - 1) x
enumFrom x = x:[ Sum n x | n <- [1 ..]]
enumFromThen x y = x:y:f (y + z) where
z = y - x
f x = x:f (x + z)
toEnum = fromIntegral
fromEnum = fromIntegral

-- d > 0
doDiv :: Nat -> Integer -> Nat
doDiv n d = f 0 n where
f _ Zero = 0
f cm (Sum x nx) = sum d (f m nx) where
(d,m) = (x + cm) `quotRem` d
sum 0 x = x
sum n x = Sum n x

doMod :: Nat -> Integer -> Nat
doMod n