[Haskell-cafe] Using GHC.Generics to print data type structure

Erik Hesselink hesselink at gmail.com
Mon Apr 14 09:00:40 UTC 2014


Instead of passing 'undefined :: a', I think the current best practice
is to pass 'Proxy :: Proxy a' (or in fact 'proxy a', i.e. be
polymorphic in the proxy). This way you can never accidentally use the
undefined value.

Erik

On Sun, Apr 13, 2014 at 4:15 PM, J. Stutterheim <j.stutterheim at me.com> wrote:
> Short, simple, thanks! Works like a charm.
>
> - Jurriën
>
> On 13 Apr 2014, at 15:36, Sjoerd Visscher <sjoerd at w3future.com> wrote:
>
>> Make the match on (x :*: y) irrefutable:
>>
>>   gprintDT ~(x :*: y) = ...
>>
>> Sjoerd
>>
>> On 13 Apr 2014, at 15:22, J. Stutterheim <j.stutterheim at me.com> wrote:
>>
>>> Hi all,
>>>
>>> I'm trying to use GHC.Generics to print a data type's structure. I have a test type TestRecord:
>>>
>>>      data TestRecord = TestRecord
>>>              { trId :: Int
>>>              , someStr :: String }
>>>              deriving Generic
>>>
>>> And a PrintDT class:
>>>
>>>      class PrintDT a where
>>>              printDT :: a -> String
>>>
>>>              default printDT :: (Generic a, GPrintDT (Rep a)) => a -> String
>>>              printDT = gprintDT . from
>>>
>>> With a corresponding instance for TestRecord. The GPrintDT class and instances are defined as follows:
>>>
>>>      class GPrintDT f where
>>>              gprintDT :: f a -> String
>>>
>>>      instance (GPrintDT a, GPrintDT b) => GPrintDT (a :*: b) where
>>>              gprintDT (x :*: y) = " { " ++ gprintDT x ++ ", " ++ gprintDT y ++ " }"
>>>
>>>      instance (Datatype d, GPrintDT f) => GPrintDT (D1 d f) where
>>>              gprintDT d = "data " ++ datatypeName d ++ " = " ++ (gprintDT $ unM1 d)
>>>
>>>      instance (Constructor c, GPrintDT f) => GPrintDT (C1 c f) where
>>>              gprintDT con
>>>                      | conIsRecord con = conName con ++ (gprintDT $ unM1 con)
>>>                      | otherwise       = "No record"
>>>
>>>      instance (Selector s, GPrintDT a) => GPrintDT (S1 s a) where
>>>              gprintDT m = selName m
>>>
>>>      instance (PrintDT a) => GPrintDT (K1 i a) where
>>>              gprintDT _ = ""
>>>
>>>      instance PrintDT Int where
>>>              printDT n = show n
>>>
>>>      instance PrintDT String where
>>>              printDT xs = xs
>>>
>>> In a first attempt, I apply printDT to a TestRecord value:
>>>
>>>      test1 :: String
>>>      test1 = printDT (TestRecord 1 "foo")
>>>
>>> This prints the expected result:
>>>
>>>      "data TestRecord = TestRecord { trId, someStr }"
>>>
>>> Now ideally, I wouldn't have to specify some value of TestRecord to get this output, since so far, I'm only printing the structure of the TestRecord type, not the values. I would want the following to give me the same result string:
>>>
>>>      test2 :: String
>>>      test2 = printDT (undefined :: TestRecord)
>>>
>>> With the current implementation, test2 gives me the following output:
>>>
>>>      "data TestRecord = TestRecord*** Exception: Prelude.undefined
>>>
>>> Is there a way to implement GPrintDT such that test2 gives me the same output as test1?
>>>
>>> Thanks!
>>>
>>> - Jurriën
>>> _______________________________________________
>>> Haskell-Cafe mailing list
>>> Haskell-Cafe at haskell.org
>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe


More information about the Haskell-Cafe mailing list