[Haskell-cafe] Best way to instance Fix?

Sam Martin sam.martin at geomerics.com
Mon May 24 08:42:10 EDT 2010


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:rwbarton at math.harvard.edu]
Sent: Mon 24/05/2010 02:28
To: Sam Martin
Cc: haskell-cafe at 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

-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20100524/b724046a/attachment.html


More information about the Haskell-Cafe mailing list