Neil Mitchell wrote:
Hi

Pretty much, yes.

So I just need to write

  newtype LazyNatural = LazyNatural [()]

or

data Nat = Zero | Succ Nat

it's your choice really.

I'm guessing there's going to be fairly minimal performance difference. (Or maybe there is. My way uses a few additional pointers. But it also allows me to elegantly recycle existing Prelude list functions, so...)

and then add some suitable instances. ;-)

Yes. Lots of them. Lots of instances and lots of methods.

Hey, the "length" function would then just be

  ln_length :: [x] -> LazyNatural
  ln_length = LazyNatural . map (const ())

Ooo, that's hard.

Nope, its really easy. Its just quite a bit of work filling in all the
instances. I bet you can't do it and upload the results to hackage
within 24 hours :-)

*ALL* the instances? No.

A small handful of them? Sure. How about this...



module LazyNatural (LazyNatural ()) where

import Data.List

newtype LazyNatural = LN [()]

instance Show LazyNatural where
 show (LN x) = "LN " ++ show (length x)

instance Eq LazyNatural where
 (LN x) == (LN y) = x == y


instance Ord LazyNatural where
 compare (LN x) (LN y) = raw_compare x y

raw_compare ([])  (_:_) = LT
raw_compare ([])  ([])  = EQ
raw_compare (_:_) ([])  = GT
raw_compare (_:x) (_:y) = raw_compare x y


instance Num LazyNatural where
 (LN x) + (LN y) = LN (x ++ y)
 (LN x) - (LN y) = LN (raw_minus x y)
 (LN x) * (LN y) = LN (concatMap (const x) y)
 negate _ = error "negate is not defined for LazyNatural"
 abs = id
 signum (LN []) = LN []
 signum (LN _)  = LN [()]
 fromInteger = LN . flip genericReplicate ()

raw_minus (_:a) (_:b) = raw_minus a b
raw_minus (a)   ([])  = a
raw_minus _     _     = error "negative result from subtraction"

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

Reply via email to