Skip to content

Instantly share code, notes, and snippets.

@JakobBruenker
Last active March 19, 2022 21:17
Show Gist options
  • Save JakobBruenker/b7f2444e47496bb26ee8cb889189ec67 to your computer and use it in GitHub Desktop.
Save JakobBruenker/b7f2444e47496bb26ee8cb889189ec67 to your computer and use it in GitHub Desktop.
Utility to show things without Show instance (but Data instance)
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE MonadComprehensions #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE DeriveDataTypeable #-}
import Data.Data
import Data.Foldable
import Data.Functor
import Data.Maybe
import Data.List
genericShow :: forall a . Data a => a -> String
genericShow a = catchAll `fromMaybe` asum [tryShow @String]
where
tryShow :: forall e . (Show e, Typeable e) => Maybe String
tryShow = cast @_ @e a <&> show
catchAll :: String
catchAll | null rest = ctr
| otherwise = "(" <> intercalate " " (ctr : rest) <> ")"
where rest = gmapQ genericShow a
ctr = show (toConstr a)
data Example = Node String Int Char Example
| Empty
deriving Data
main :: IO ()
main = putStrLn . genericShow $ Node "foo" 1 'a' $ Node "bar" 42 'b' Empty
-- Output:
-- (Node "foo" 1 'a' (Node "bar" 42 'b' Empty))
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment