RE: [Haskell-cafe] Best way to instance Fix?

2010-05-24 Thread Sam Martin

That's great, thanks. Looks like FlexibleContexts is redundant (effectively a 
subset of UndecidableInstances?).

Ivan, I hadn't realised, but I had FlexibleInstances on before for other 
reasons. I guess that's why I ccould get the workaround to compile. 

Cheers,
Sam

-Original Message-
From: Reid Barton [mailto:rwbar...@math.harvard.edu]
Sent: Mon 24/05/2010 02:28
To: Sam Martin
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Best way to instance Fix?
 
On Mon, May 24, 2010 at 02:13:32AM +0100, Sam Martin wrote:
 
 Hi!
 
 I'm trying to work out the best way to generate (ideally derive) instances 
 for the Fix type. Here's a cut down example:
 
 data Greet x = AlloAllo x x | AuRevoir deriving Show
 newtype Fix f = In { out :: f (Fix f) } -- deriving Show -- DOESN'T COMPILE
 
 -- workaround
 instance Show (Fix Greet) where show (In i) = In  ++ show i
 
 In other words, given a number of parametised types that I can derive, say, 
 Ord, Eq and Show for, how should I go about getting the instances for the 
 Fix-d version of them as well? I've tried a few things, but no luck so far. 
 
 Any clues?

You can use GHC's standalone deriving mechanism for this, described at
http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/deriving.html


{-# LANGUAGE StandaloneDeriving, FlexibleContexts, UndecidableInstances #-}

data Greet x = AlloAllo x x | AuRevoir deriving Show
newtype Fix f = In { out :: f (Fix f) }

deriving instance Show (f (Fix f)) = Show (Fix f)


Regards,
Reid Barton

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


Re: [Haskell-cafe] Best way to instance Fix?

2010-05-23 Thread Ivan Miljenovic
On 24 May 2010 11:13, Sam Martin sam.mar...@geomerics.com wrote:

 Hi!

 I'm trying to work out the best way to generate (ideally derive) instances
 for the Fix type. Here's a cut down example:

 data Greet x = AlloAllo x x | AuRevoir deriving Show
 newtype Fix f = In { out :: f (Fix f) } -- deriving Show -- DOESN'T COMPILE

I think this is because for Fix to have a Show instance, it needs f to
have a Show instance, which only works if the parameter passed to it
has a Show instance, which means Fix needs to have a Show instance,
etc.  My guess is that the deriving tool doesn't like infinite
loops...

 -- workaround
 instance Show (Fix Greet) where show (In i) = In  ++ show i

Are you using OverlappingInstances or something to get this to work?

 In other words, given a number of parametised types that I can derive, say,
 Ord, Eq and Show for, how should I go about getting the instances for the
 Fix-d version of them as well? I've tried a few things, but no luck so far.

Does (==) = (==) `on` out works for the Eq instance?

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Best way to instance Fix?

2010-05-23 Thread Reid Barton
On Mon, May 24, 2010 at 02:13:32AM +0100, Sam Martin wrote:
 
 Hi!
 
 I'm trying to work out the best way to generate (ideally derive) instances 
 for the Fix type. Here's a cut down example:
 
 data Greet x = AlloAllo x x | AuRevoir deriving Show
 newtype Fix f = In { out :: f (Fix f) } -- deriving Show -- DOESN'T COMPILE
 
 -- workaround
 instance Show (Fix Greet) where show (In i) = In  ++ show i
 
 In other words, given a number of parametised types that I can derive, say, 
 Ord, Eq and Show for, how should I go about getting the instances for the 
 Fix-d version of them as well? I've tried a few things, but no luck so far. 
 
 Any clues?

You can use GHC's standalone deriving mechanism for this, described at
http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/deriving.html


{-# LANGUAGE StandaloneDeriving, FlexibleContexts, UndecidableInstances #-}

data Greet x = AlloAllo x x | AuRevoir deriving Show
newtype Fix f = In { out :: f (Fix f) }

deriving instance Show (f (Fix f)) = Show (Fix f)


Regards,
Reid Barton
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe