How to Show a Constructor
How to show a (toplevel) constructor in a generic way? (Pun intended.)
Not really a complicated thing but I thought that it might be nice, simple, and
yet valuable example for generic programming in Haskell using GHC.Generics
.
Here is the code.
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE TypeOperators #-}
module Data.Generics.ShowConstructor
( showConstrwhere
)
import Data.Function ((.))
import Data.String (String)
import GHC.Generics
:+:)(L1, R1), C, Constructor, Generic, M1(M1), Rep, conName,
((
from)
class ShowConstr f where
gShowConstr :: f p -> String
instance (ShowConstr a, ShowConstr b) => ShowConstr (a :+: b) where
L1 x) = gShowConstr x
gShowConstr (R1 x) = gShowConstr x
gShowConstr ({-# INLINE gShowConstr #-}
instance {-# OVERLAPPABLE #-} ShowConstr a => ShowConstr (M1 i c a) where
M1 x) = gShowConstr x
gShowConstr ({-# INLINE gShowConstr #-}
instance Constructor c => ShowConstr (M1 C c a) where
= conName
gShowConstr {-# INLINE gShowConstr #-}
showConstr :: (Generic a, ShowConstr (Rep a)) => a -> String
= gShowConstr . from
showConstr {-# INLINE showConstr #-}
Now let’s talk about it a little.
Usual questions I get from people dipping their toes to Generics
for the
firs time are:
- Why do I need to create the class?
- Why are there so many instances?
- What are these types for which there are instance for?
- Why there is
ShowConstr (Rep a)
constraint in type ofshowConstr
?
Class Generics
has not only associated functions
from :: a -> Rep a x
and to :: Rep a x -> a
(ignore x
for now), but also type (family) Rep a
, representation of type a
.
This type is built out of only very few other types (see Generics documentation on
Hackage).
(Couple more than I have instances for, but I do not need them in my case.)
To be able to traverse this type, we use Haskell-s ad-hoc polymorphism mechanism,
type classes. Take for example Instance ShowConstr (M1 i c a)
.
We do not know type of x
in M1 x
, and yet we want to process it.
And type classes are Haskell-s answer for this sort of problem :-)
.
And just to wrap things up: if you have instances for
Data.Data.Data
, you can indeed go for slightly simpler solution.
import Data.Data (Data, toConstr)
showConstr :: Data a => a -> String
= show . toConstr showConstr
Or yet even (in some sense) simpler, requiring only Text.Show.Show
(but with some trouble-causing corner cases (Lists, Strings, and more generally
types with custom Show instance, …)).
showConstr :: Show a => a -> String
= takeWhile (not . isSpace) . show showConstr