Core questions

Sean Leather leather at cs.uu.nl
Mon Feb 2 05:56:15 EST 2009


Hi Matthijs,

This is a shameless plug for EMGM, a library for generic programming that
we've been working on at Utrecht.

| However, there are two issues bothering me still. The first is that the
> | Core types (in particular CoreExpr) are not instances of Show. They are
> | instances of Outputable, which allows them to be pretty printed.
> | However, this pretty printing is good to view the structure of the
> | expression that the CoreExpr represents, but doesn't show the structure
> | of the CoreExpr itself. For example, tuple construction is printed
> | simply as (a, b), while the actual core expression is a nested
> | application of two types, and a and b to the GHC.Tuple.(,) function
> | (or datacon?). Also, the exact constructors used are not quite clear,
>
> There's absolutely no reason why
>        CoreExpr
>        CoreBind
>        Type
> should not be an instance of Show.  It'd take you 10 mins to make it so,
> with the aid of 'standalone deriving' (described in the GHC user manual).
>
> There *is* a reason why TyCon and Class are not:
>        a TyCon
>        enumerates its DataCons
>        whose type mentions the TyCon
>
> In short, the data structures are, by design, cyclic.  Printing one of
> these would take a long time.
>
> But I bet you could get a long way with the three above, plus just printing
> the *name* of a TyCon or Class or Id.  Something like:
>        instance Show TyCon where
>           show tc = showSDoc (ppr tc)
>

Suppose you want to print a type with the exception of one constructor,
because it is mutually recursive with another or just prints out lots of
useless information. There are at least two ways to do it, one with EMGM,
and one with standalone deriving. I show both below.

> {-# LANGUAGE TemplateHaskell #-}
> {-# LANGUAGE FlexibleInstances #-}
> {-# LANGUAGE FlexibleContexts #-}
> {-# LANGUAGE MultiParamTypeClasses #-}
> {-# LANGUAGE OverlappingInstances #-}
> {-# LANGUAGE UndecidableInstances #-}
> {-# LANGUAGE StandaloneDeriving #-}
>
> module Example where
>
> import qualified Generics.EMGM as G
>
> -----------------------------------------
>
> data A = A0 Int  | A1 B
> data B = B0 Char | B1 A
>
> $(G.derive ''A)
> $(G.derive ''B)
>
> instance G.Rep G.Show B where
>   rep = G.Show (\_ _ -> f)
>     where
>       f (B0 c) = showString "(B0 " . showChar c . showString ")"
>       f (B1 _) = showString "(B1 <some A>)"
>
> valAB = A1 (B1 (A0 37))
> showAB = G.show valAB
>
> -----------------------------------------
>
> data C = C0 Int  | C1 D
> data D = D0 Char | D1 C
>
> deriving instance Show C
> instance Show D where
>   showsPrec _ = f
>     where
>       f (D0 c) = showString "(D0 " . showChar c . showString ")"
>       f (D1 _) = showString "(D1 <some C>)"
>
> valCD = C1 (D1 (C0 37))
> showCD = show valCD
>
> -----------------------------------------

The first one uses EMGM's Template Haskell-based derive function to generate
the type representation. I then give an overriding instance for the generic
Show function (where G.Show is a newtype used for all show/shows/showsPrec
generic functions). So, the constructor B1 will not print out the value of
its A-type argument.

The second uses standalone deriving and a handwritten instance for D that
does the same thing as the first solution did for B.

What's the difference? Well, between these instances of G.Show and Show,
there's not much. However, the EMGM approach gives you access to a lot of
other generic functions including Read, Crush, Collect, etc. See the
documentation for all of them [1].

One function you may be able to take advantage of is 'collect', perhaps to
collect the B values in valAB.

*Example> G.show (G.collect valAB :: [B])
"[(B1 <some A>)]"

Moral of the story: you can do it either way, but EMGM gives you a lot
extra.

Apologies for the self-promotion, but we're looking for people who might
want to use EMGM. ;) If you have feedback, let us know! [2]

Regards,
Sean

[1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/emgm
[2] http://www.cs.uu.nl/wiki/GenericProgramming/EMGM
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20090202/863a9741/attachment.htm


More information about the Glasgow-haskell-users mailing list