Splitting SYB from the base package in GHC 6.10

Ian Lynagh igloo at earth.li
Tue Sep 2 08:35:23 EDT 2008


On Mon, Sep 01, 2008 at 02:49:01PM +0200, José Pedro Magalhães wrote:
> 
> with the "dubious" Data instances

FWIW, I don't believe in "dubious" instances. There are two reasons one
might want to not have an instance:

* You want to use a different instance for the same type, e.g. you want
  the (Ratio t) instance to descend into the t rather than just treating
  the type abstractly.

  This sounds nice in theory, but it is flawed in practice. Instances
  are global in Haskell, so if one library needs Ratio instance 1, and
  another library needs Ratio instance 2, then those libraries cannot be
  used in the same program.

* You don't want to actually use Data with that type, and you want the
  compiler to tell you if a bug in your code means that the instance
  would be used ("Can't find instance Data (IO a)").

  However, in my (admittedly not vast) experience, this isn't a problem
  that tends to crop up in practice. Also, note that the presence of
  these instances doesn't affect correct programs.

Also, I've just spent a couple of minutes staring at the SYB and
SBY-With-Class Data classes; am I right in thinking that neither can be
implemented on top of the other? Here's part of the classes:

------------------------------------------------
{-# LANGUAGE UndecidableInstances, OverlappingInstances, FlexibleInstances,
             MultiParamTypeClasses, Rank2Types,
             ScopedTypeVariables,
             EmptyDataDecls, KindSignatures #-}

import Data.Typeable

class Typeable a => Data1 a where
    gfoldl1 :: (forall b c. Data1 b => w (b -> c) -> b -> w c)
            -> (forall g. g -> w g)
            -> a -> w a

class (Typeable a, Sat (ctx a)) => Data2 ctx a where
    gfoldl2 :: Proxy ctx
            -> (forall b c. Data2 ctx b => w (b -> c) -> b -> w c)
            -> (forall g. g -> w g)
            -> a -> w a

data Proxy (a :: * -> *)

class Sat a where
    dict :: a
------------------------------------------------

Could uniplate etc have been built on top of SYBWC's Data, instead of
SYB's Data? Is SYB's Data the basic building block only because there
are more instances for it in the wild, and GHC can derive them?


Thanks
Ian



More information about the Libraries mailing list