Functional Dependencies

Iavor Diatchki iavor.diatchki at gmail.com
Tue Aug 16 13:45:41 EDT 2005


Hello,
I am not sure what GHC is doing, it certainly seems to be
inconsistent.  In Hugs both the examples work.  In case you are
interested, here is how you can get a version that works in
both Hugs and GHC (I just modified your code a little):

{-# OPTIONS -fglasgow-exts -fallow-undecidable-instances #-}

module Add where

data Zero;  zero = undefined :: Zero
newtype Succ n  = Succ n

class Add n m s | n m -> s where
  add :: n -> m -> s
  add  = undefined

instance Add Zero m m
instance Add n m s => Add (Succ n) m (Succ s)

class Fib n f | n -> f where
  fib :: n -> f
  fib = undefined

instance Fib Zero (Succ Zero)
instance Fib (Succ Zero) (Succ Zero)
instance (Fib n fib_n,
          Fib (Succ n) fib_s_n,
          Add fib_n fib_s_n sum
         ) => Fib (Succ (Succ n)) sum

eight = fib (Succ (Succ (Succ (Succ (Succ zero)))))
two   = add (Succ zero) (Succ zero)


*Add> :t eight
eight :: Succ (Succ (Succ (Succ (Succ (Succ (Succ (Succ Zero)))))))
*Add> :t two
two :: Succ (Succ Zero)

-Iavor

On 8/16/05, Dirk Reckmann <reckmann at cs.tu-berlin.de> wrote:
> Hello Keean!
> 
> Am Dienstag, 16. August 2005 13:48 schrieb Keean Schupke:
> > Picked up on this late... I have working examples of add etc under
> > ghc/ghci...
> > I can't remeber all the issues involved in getting it working, but I can
> > post the
> > code for add if its any use?
> 
> Yes, that would be nice. I'd like to see 'add' working... However, after each
> answer to my posting, I get more confused. Simon Peyton-Jones took all of my
> hope to get it working, because ghc doesn't like universal quantified but
> uniquely idetified types (at least, this is my understanding of his email).
> Now you have a working 'add' typelevel program. And the most confusing part
> for me is, that my fibonacci number program works, even though it makes use
> of the not working version of add.
> 
> So, I'm really looking forward to your version!
> 
> Ciao,
>   Dirk
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>


More information about the Glasgow-haskell-users mailing list