`show` record without deriving Show - haskell

Quite often I need to print something while debugging and unless the datatype I need to see derives Show I can't print it. For some datatypes I can't add deriving (Show) to the definition because it may be in a library or somewhere else I can't get to.
Is there anyway I can print these datatypes for debugging?

Standalone deriving
A deriving clause on the type definition isn't the only way to derive. You can also use the StandaloneDeriving GHC language extension.
λ> :set -XStandaloneDeriving
λ> data Person = Human { name :: String, age :: Int } | Dog { goodPupper :: Bool }
λ> deriving instance Show Person
λ> Human "Chris" 31
Human {name = "Chris", age = 31}
Generics
If the type has a Generic instance, you can stringify it with the gshowsPrecdefault function from the generic-deriving package.
λ> import GHC.Generics
λ> import Generics.Deriving.Show
λ> data Person = Human { name :: String, age :: Int } | Dog { goodPupper :: Bool } deriving Generic
λ> putStrLn $ gshowsPrecdefault 0 (Dog True) ""
Dog {goodPupper = True}
GHCi :force
You can use the :force command in GHCi to inspect a value.
λ> data Person = Human { name :: String, age :: Int } | Dog { goodPupper :: Bool }
λ> x = Human "Chris" 31
λ> x
<interactive>:17:1: error:
• No instance for (Show Person) arising from a use of ‘print’
• In a stmt of an interactive GHCi command: print it
λ> :force x
x = <Human> "Chris" 31
See Breakpoints and inspecting variables in the GHC manual.

You have to make your datatype an instance of Show if you want to print it in any way. If you don't want to derive Show you can always implement it yourself.
data Foo = Bar
instance Show Foo where
show Bar = "This is Bar"
main = print f where f = Bar

You can absolutely print things without Show instances.
data MyType a = MyType Int a
showMyType :: (a -> String) -> MyType a -> String
showMyType f (MyType n a) =
"MyType " ++ show n ++ " (" ++ f a ++ ")"

Related

Get all fields of a Haskell data contructor

Suppose I have the following data type which maps my database schema.
data Object = Object
{ classification :: Text
, country :: Text
, numberOfParts :: Int
-- Lots of other fields
}
I want to extract statistics for all objects in the database. For example, I want to extract the frequency of every field in the Person data constructor. So I would have the following function :
-- In the return type, the key of the Map is the field name.
-- Each map value represents possible values with frequency
-- (ex. "classification" -> [("table", 10), ("chair", 3), ("computer", 2)])
generateStats :: [Object] -> Map Text [(Text, Integer)]
This function would calculate the frequency of every field, so I would have to call id object, classification object, country object, etc. If the datatype has 50 fields, I would have to call 50 functions to access those fields.
Is there a way to generalize this ?
Can it be generalized to any data constructor ?
Is there a more elegant way to solve this type of problem ?
This sort of problem can be solved with generics. Usually, the syb package (Data.Generics or Data.Data or SYB or "scrap your boilerplate" generics) is the easiest to use, so it's worth trying it first and moving on to more complicated libraries only if you can't get it to work for a particular task.
Here, syb provides a straightforward way of retrieving the list of field names from a record constructor. If you derive a Data instance for some Object:
{-# LANGUAGE DeriveDataTypeable #-}
import Data.Generics
import Data.Text (Text)
import qualified Data.Text as Text
data Object = Object
{ classification :: Text
, country :: Text
, numberOfParts :: Int
} deriving (Data)
then you can fetch the field names at runtime with the following function:
-- Get field names (empty list if not record constructor)
getnames :: Data object => object -> [Text]
getnames = map Text.pack . constrFields . toConstr
like so:
λ> :set -XOverloadedStrings
λ> getnames $ Object "prime" "Canada" 5
["classification","country","numberOfParts"]
You can fetch field values as Text at runtime using a generic query gmapQ and writing a generic helper function toText that converts field values of various types to Text:
-- Get field values as Text.
getfields :: Data object => object -> [Text]
getfields = gmapQ toText
The toText function has type:
toText :: (Data a) => a -> Text
and needs to be prepared to handle any possible field encountered. A limitation of Data.Data generics is that you can only handle a fixed set of explicit types with a default value for "the rest". Here, we handle Text, String, Int, and Double types and throw an error with unknown for "the rest":
{-# LANGUAGE TypeApplications #-}
toText = mkQ unknown -- make a query with default value "unknown"
id -- handle: id :: Text -> Text
`extQ` Text.pack -- extend to: pack :: String -> Text
`extQ` tshow #Int -- extend to: tshow :: Int -> Text
`extQ` tshow #Double -- extend to: tshow :: Double -> Text
where tshow :: (Show a) => a -> Text
tshow = Text.pack . show
unknown = error "unsupported type"
If you wanted to handle all types with a Show (or some other) instance, then syb won't do the job. (If you tried dropping the type application above and writing `extQ` tshow to handle all Show cases, you'd get an error.) Instead, you'd need need to upgrade to syb-with-class or some other generics library to handle this.
With all that in place, getting a list of key/value pairs from any object is straightword:
getpairs :: Data object => object -> [(Text,Text)]
getpairs = zip <$> getnames <*> getfields
This works on Objects:
λ> concatMap getpairs [Object "prime" "Canada" 5, Object "substandard" "Fakeistan" 100]
[("classification","prime"),("country","Canada"),("numberOfParts","5")
,("classification","substandard"),("country","Fakeistan"),("numberOfParts","100")]
or anything else with a Data instance. Sum types and record-less constructors should work okay. With the type:
data OtherObject = Foo { foo :: String, factor :: Double }
| Bar { bar :: Int }
| NotARecord Int Int Int
deriving (Data)
we get:
λ> getpairs $ Foo "exchange" 0.75
[("foo","exchange"),("factor","0.75")]
λ> getpairs $ Bar 42
[("bar","42")]
λ> getpairs $ NotARecord 1 2 3
[]
Here's a complete code example:
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
import Data.Generics
import Data.Text (Text)
import qualified Data.Text as Text
data Object = Object
{ classification :: Text
, country :: Text
, numberOfParts :: Int
} deriving (Data)
data OtherObject = Foo { foo :: String, factor :: Double }
| Bar { bar :: Int }
| NotARecord Int Int Int
deriving (Data)
-- Get field names (empty list if not record constructor)
getnames :: Data object => object -> [Text]
getnames = map Text.pack . constrFields . toConstr
-- Get field vales as Text.
getfields :: Data object => object -> [Text]
getfields = gmapQ toText
-- Generic function to convert one field.
toText :: (Data a) => a -> Text
toText = mkQ unknown -- make a query with default value "unknown"
id -- handle: id :: Text -> Text
`extQ` Text.pack -- extend to: pack :: String -> Text
`extQ` tshow #Int -- extend to: tshow :: Int -> Text
`extQ` tshow #Double -- extend to: tshow :: Double -> Text
where tshow :: (Show a) => a -> Text
tshow = Text.pack . show
unknown = error "unsupported type"
-- Get field name/value pairs from any `Data` object.
getpairs :: Data object => object -> [(Text,Text)]
getpairs = zip <$> getnames <*> getfields
main :: IO ()
main = mapM_ print $
[ getpairs $ Object "prime" "Canada" 5
, getpairs $ Foo "exchange" 0.75
, getpairs $ Bar 42
, getpairs $ NotARecord 1 2 3
]
This solution depends on the generics machinery from generics-sop and the streaming sinks from foldl.
Some required pragmas and imports:
{-# LANGUAGE DeriveGeneric,DeriveAnyClass,ScopedTypeVariables,FlexibleContexts,
GADTs,TypeApplications,OverloadedStrings,StandaloneDeriving, TypeOperators #-}
module Main (main) where
import qualified GHC.Generics as GHC
import Generics.SOP (All,And,IsProductType,productTypeFrom,
DatatypeInfo(..),datatypeInfo,
ConstructorInfo(..),FieldInfo(..),FieldName,
projections, I(..), K(..),type (-.->)(Fn),type (:.:)(Comp),
Generic,HasDatatypeInfo)
import Generics.SOP.NP -- All the *_NP functions come form here
import Generics.SOP.Dict (Dict(..),zipAll)
import qualified Control.Foldl as L
import Data.Proxy
import Data.Text (Text)
import qualified Data.Map.Strict as Map
Datatypes and functions to calculate histograms, which aren't tied to any concrete record:
newtype Histogram a = Histogram (Map.Map a Int) deriving Show
-- Hides the exact type of the key behind an existential
data SomeHistogram = forall a. (Ord a, Show a) => SomeHistogram (Histogram a)
deriving instance Show SomeHistogram
-- Streaming sink for a single field
histogram :: Ord a => L.Fold a (Histogram a)
histogram = (L.Fold step Map.empty Histogram)
where
step m a = Map.insertWith (+) a 1 m
-- For any record with Generics.SOP.Generic instance,
-- create a streaming sink that accepts record values and
-- returns a list of histograms, one for each field
recordHistogram :: forall r xs . (IsProductType r xs, All Ord xs, All Show xs)
=> L.Fold r [SomeHistogram]
recordHistogram =
let productOfFolds =
cliftA_NP
(Proxy #Ord)
(\(Fn proj) ->
Comp (L.premap (\o -> let np = productTypeFrom #r #xs o
I r = proj (K np)
in r)
histogram))
(projections #xs)
foldToProduct = sequence'_NP productOfFolds -- pull the Fold outward
-- convince GHC that we have a combination of Ord and Show for all fields
ordAndShow = zipAll (Dict #(All Ord) #xs) (Dict #(All Show) #xs)
foldToList = case ordAndShow of -- collapse result of Fold into a list
Dict -> collapse_NP . cliftA_NP (Proxy #(Ord `And` Show)) (K . SomeHistogram)
<$>
foldToProduct
in foldToList
In case we want a list of field names to zip with the list of histograms:
fieldNamesOf :: forall r xs. (IsProductType r xs, HasDatatypeInfo r)
=> Proxy r
-> [FieldName]
fieldNamesOf _ =
case datatypeInfo (Proxy #r) of
ADT _ _ ((Record _ fields) :* Nil) _ ->
collapse_NP (liftA_NP (\(FieldInfo i) -> K i) fields)
_ -> error "hey, not a record!"
Putting it all to work with Object:
data Object = Object
{ classification :: Text
, country :: Text
, numberOfParts :: Int
} deriving (GHC.Generic,Generic,HasDatatypeInfo)
-- Generic and HasDatatypeInfo from generics-sop
main :: IO ()
main = print $ L.fold recordHistogram [Object "foo" "Spain" 4, Object "bar" "France" 4]
This solution has two potential problems:
Internally, recordHistogram uses n-ary products from generics-sop. Constructing and traversing these products might incur in some overhead.
There might be some space leak in the streaming sink (the Fold) returned by recordHistogram. Some extra strictness might be necessary.

Cannot print own data type in Haskell

Please read my problem below, after the bold text, before taking your time to scrutinize this code. I don't want to waste your time if you can't answer this.
Okay. I have created my own data type within Haskell. It is
data Dialogue= Choice String [(String, Dialogue)]
| Action String Event
-- deriving (Show)
Note the commented out 'deriving (Show)' which is important for my problem below.
I have a function named dialogue defined as
dialogue:: Game -> Dialogue -> IO Game
dialogue (Game n p ps) (Action s e) = do
putStrLn s
return (e (Game n p ps))
dialogue (Game n p ps) (Choice s xs) = do
putStrLn s
let ys = [ fst a | a <- xs ]
let i = [1..length ys]
putStrLn (enumerate 1 ys)
str <- getLine
if str `elem` exitWords
then do
return (Game n p ps)
else do
let c = read str::Int
if c `elem` i
then do
let ds = [ snd b | b <- xs ]
let d = ds !! c
putStrLn $ show d
return (Game n p ps)
else do
error "error"
My data type game is defined as
data Game = Game Node Party [Party] | Won
deriving (Eq,Show)
And an Event is a type, defined by myself as
type Event = Game -> Game
Now, this is where my problem occurs. When I go to load this file within cmd and I have not included deriving (Show) within my data type Dialogue, I get the following error:
* No instance for (Show Dialogue) arising from a use of `show'
* In the second argument of `($)', namely `(show d)'
In a stmt of a 'do' block: putStrLn $ (show d)
In the expression:
do let ds = ...
let d = ds !! c
putStrLn $ (show d)
return (Game n p ps)
|
120 | putStrLn $ (show d)
It would seem to me that I need to include the deriving (Show) in order to be able to print this data type to the console. However, when I do include deriving (Show), I get this error:
* No instance for (Show Event)
arising from the second field of `Action' (type `Event')
(maybe you haven't applied a function to enough arguments?)
Possible fix:
use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
* When deriving the instance for (Show Dialogue)
|
85 | deriving Show
I have spent quite a long time trying to find out why this might be happening. But I cannot find anywhere online that seems to document this particular problem.
Any help would be perfect, or even just a link to an appropriate explanation.
**Edit: ** My Event is a type synonym and so I cannot add deriving Show to this
Thanks a lot
Event as you have defined it is a function which has no sensible method to show. How would you like to display this information? One solution is to import Text.Show.Functions, which has an instance.
For example:
Prelude Text.Show.Functions> show (+ 1)
"<function>"
Another solution is to define your own show instance:
instance Show (a -> b) where
show _ = "_"
type Event = Game -> Game
data Dialogue= Choice String [(String, Dialogue)]
| Action String Event
-- deriving (Show)
When compiler tries to derive Show for Dialogue, it has to Show an Event in the Action variant, but it can't — Event is a function, and functions don't get auto-derived Show instances.
You have to manually implement either Show Event or Show Dialogue. One way to implement Show Dialogue would be this:
instance Show Dialogue where
show (Choice s ds) = " " `intercalate` ["Choice", show s, show ds]
show (Action s e) = " " `intercalate` ["Action", show s]

Haskell Type Polymorphism -- Mapping to String

I am new to Haskell, so maybe I am missing some fundamental concepts here (or maybe failed to find the appropriate extension). I was wondering if there was a way to optimize or further abstract the following scenario. This code seems very redundant.
Let's say I have the following data classes:
data Person = Person
{ personName :: !String
, personAge :: !Int
} deriving Show
data Dog = Dog
{ dogName :: !String
, dogAge :: !Int
} deriving Show
Let's say I have a service and I'm only concerned with outputing records as strings. In reality, the strings will probably be JSON and the records fetched from the DB, but let's take a simpler case. I basically need a URL token to fetch an appropriate object (say, the string "dog" will get me a Dog, or even just the Haskell "show" string, without expressly declaring it as (value)::Dog).
I have attempted to implement this in several ways...the only thing that seems to work is the following:
data Creature = DogC Dog
| PersonC Person
deriving Show
fromString :: String -> Maybe Creature
fromString "dog" = Just $ DogC $ Dog "muffin" 8
fromString "person" = Just $ PersonC $ Person "John" 22
fromString _ = Nothing
main :: IO ()
main = do
putStrLn $ show $ fromString "dog"
I'm not entirely fond of the new type, nor the list of fromString declarations. And to benefit from the original data declarations, I would probably need to write a similarly tedious expression (eg, "fromCreature") to revert Creature back into my original types. This information might change, so I would probably need TH for a few of the declarations...
Is there a way around some of this? I fiddled with GADTs and classes, but both seemed to be dependent on type- rather than value- based polymorphism (A string identifier tends to cause issues with ambiguous instances). It would be nice to map the constructor to a string (Say, with Data.Map), but constructors often have different kinds.
Update
So, I went with an approach that isn't exactly relevant to the question I had asked, but it may be useful to someone. I did want to maintain some record types, but most didn't add much value and were getting in my way. The steps I had followed went something like:
Use a different/lower-level DB driver, that returns workable types (eg, [ColumnDef] and [[SQLValue]] instead of tuples and records...).
Create ToJSON instances for SQLValue -- most of the types were covered, except a few ByteString types, and I had to handle the conversion of SQLNull to Null. To maintain compatibility with some record types, my default handler looked like: toJSON = genericToJSON defaultOptions { sumEncoding = UnTaggedValue} The untagged value should allow one to read the JSON into defined data types (eg, Dog / Person ) if desired....
Given that column name is accessible from ColumnDef, I wrote an expression that zips [ColumnDef] and [SqlValue] to a list of Aeson-compatible key-value pairs, eg: toJsPairs :: [ColumnDef] -> [SqlValue] -> [(Text,Value)]
Then, I wrote an expression to fetch the JSON from a table name, which more or less serves as my "universal dispatcher." It references a list of authorized tables, so it's less crazy than it might sound.
The code looked a bit like this (using mysql-haskell).
{-# LANGUAGE OverloadedStrings #-}
import qualified Control.Applicative as App
import Database.MySQL.Base
import qualified System.IO.Streams as Streams
import Data.Aeson (FromJSON, ToJSON)
import Data.Aeson.Encode.Pretty (encodePretty)
import Data.Aeson.Types
import Data.Text.Encoding
import Data.String (fromString)
import Data.ByteString.Internal
import qualified Data.ByteString.Lazy.Internal as BLI
import Data.HashMap.Strict (fromList)
appConnectInfo = defaultConnectInfo {
ciUser = "some_user"
, ciPassword = "some_password"
, ciDatabase = "some_db"
}
instance FromJSON ByteString where
parseJSON (String s) = pure $ encodeUtf8 s
parseJSON _ = App.empty
instance ToJSON ByteString where
toJSON = String . decodeUtf8
instance ToJSON MySQLValue where
toJSON (MySQLNull) = Null
toJSON x = genericToJSON defaultOptions
{ sumEncoding = UntaggedValue } x
-- This expression should fail on dimensional mismatch.
-- It's stupidly lenient, but really dimensional mismatch should
-- never occur...
toJsPairs :: [ColumnDef] -> [MySQLValue] -> [(Text,Value)]
toJsPairs [] _ = []
toJsPairs _ [] = []
toJsPairs (x:xs) (y:ys) = (txt x, toJSON y):toJsPairs xs ys
where
-- Implement any modifications to the key names here
txt = decodeUtf8.columnName
listRecords :: String -> IO BLI.ByteString
listRecords tbl = do
conn <- connect appConnectInfo
-- This is clearly an injection vulnerability.
-- Implemented, however, the values for 'tbl' are intensely
-- vetted. This is just an example.
(defs, is) <- query_ conn $ fromString ( "SELECT * FROM `" ++ tbl ++ "` LIMIT 100")
rcrds <- Streams.toList is
return $ encodePretty $ map (jsnobj defs) rcrds
where
jsnobj :: [ColumnDef] -> [MySQLValue] -> Value
jsnobj defs x = Object $ fromList $ toJsPairs defs x
If what you want to consume at the end is json value - it might make sense to
represent result as json value using aeson library:
{-# LANGUAGE DeriveGeneric #-}
import Data.Aeson
import GHC.Generics
data Dog = Dog Int String deriving (Show, Generic)
data Cat = Cat Int String deriving (Show, Generic)
-- here I'm using instance derived with generics, but you can write one by
-- hands
instance ToJSON Dog
instance ToJSON Cat
-- actions to get stuff from db
getDog :: Monad m => Int -> m Dog
getDog i = return (Dog i (show i))
getCat :: Monad m => Int -> m Cat
getCat i = return (Cat i (show i))
-- dispatcher - picks which action to use
getAnimal :: Monad m => String -> Int -> m (Maybe Value)
getAnimal "dog" i = Just . toJSON <$> getDog i
getAnimal "cat" i = Just . toJSON <$> getCat i
getAnimal _ _ = return Nothing
main :: IO ()
main = do
getAnimal "dog" 2 >>= print
getAnimal "cat" 3 >>= print
getAnimal "chupakabra" 12 >>= print
High energy magic version
class Monad m => MonadAnimal m where
-- basically you want something that fetches extra argumets from HTTP or
-- whatevere, perform DB query and so on.
class Animal a where
animalName :: Proxy a -> String
animalGetter :: MonadAnimal m => m a
locateAnimals :: MonadAnimal m => Q [(String, m Value)]
locateAnimals -- implement using TH (reify function is your friend). It should look for
-- all the animal instances in scope and make a list from them with serialized
-- fetcher.
-- with that in place dispatcher should be easy to implement

Sort list of different types

I'd like to sort a list of two different types. To do so I first create a Wrappertype, so I can mappend both types.
Is having a Wrapper type the right way here?
I'm not clear on how do I do the actual sorting if I'd like to sort by the delta key (i.e. fooDelta and barDelta)
The code:
import Data.List (sortBy)
import Data.Monoid
import Data.Ord (comparing)
data Foo = Foo
{ fooLabel :: String
, fooDelta :: Int
} deriving (Show, Eq)
data Bar = Bar
{ barLabel :: String
, barDelta :: Int
, barAnother :: String
} deriving (Show, Eq)
data Wrapper = WFoo Foo | WBar Bar
deriving (Show, Eq)
sortTest :: [Wrapper]
sortTest =
listFoo <> listBar
where
listFoo = [WFoo $ Foo "label1" 0, WFoo $ Foo "label2" 2]
listBar = [WBar $ Bar "label1" 1 "another1"]
A wrapper type is definitely a good way to do this. Since you simply want to sort your wrapped values based on a constituent Int value, you can use Data.List.sortOn.
Define a function which extracts the delta value:
delta :: Wrapper -> Int
delta (WFoo f) = fooDelta f
delta (WBar b) = barDelta b
Then use sortOn like this:
main :: IO ()
main = print $ sortOn delta sortTest
This gives the following output for your example:
[WFoo (Foo {fooLabel = "label1", fooDelta = 0}),WBar (Bar {barLabel = "label1", barDelta = 1, barAnother = "another1"}),WFoo (Foo {fooLabel = "label2", fooDelta = 2})]
Another way to do this is to define an Ord instance for your wrapper type. Then you can simply use sort on your [Wrapper] list.

Dynamically retrieve values of a data type

I'm using the Data.Data module to dynamically grab some data of a data type at runtime. Let's say a have a data type like data Place = Place {name :: Text, description :: Text} deriving (Data):
I could retrieve its constructor with toConstr toConstr (Place "Some place" "Bla") which will give me Place
I could retrieve its label fields with constrFields constrFields $ toConstr (Place "Some place" "Bla") which will give me ["name", "description"]
Now what I need is to get the values with which I constructed the Place, so for Place "Some place" "Bla" I want to extract something like ["Some place", "Bla"], the catch being that in my code I don't know that this data value is a Place, it could be any data type that derives the Data class. Icn code:
getValuesOfDataValue :: (Data a) => a -> [String]
getValuesOfDataValue a =
-- some magic generic function
data Place = Place {name :: Text, description :: Text} deriving (Data)
-- the code below should evaluate to ["Some place", "Bla"]
getValuesOfDataValue (Place "Some place" "Bla")
data SomeType = SomeType {num :: Integer, num2 :: Integer} deriving (Data)
-- the code below should evaluate to [300, 500]
getValuesOfDataValue (SomeType 300 500)
How can I accomplish this?
Note: getValuesOfDataValue doesn't have to return exactly a [String] type, it just need to have the values packed in something.
Use cast from the Typeable family (recall that Data is a subclass of Typeable).
λ> import Data.Text
λ> import Data.Data
λ> :set -XDeriveDataTypeable -XOverloadedStrings
λ> data Triple = Triple Text Text Int deriving (Show, Data)
λ> gmapQ cast (Triple "a" "b" 1821) :: [Maybe Text]
[Just "a",Just "b",Nothing]
λ> gmapQ cast (Triple "a" "b" 1821) :: [Maybe Int]
[Nothing,Nothing,Just 1821]
Take that, dynamically typed programming languages.
If you don't know which type you want in advance, you can also stringify the values with gshow from the syb package:
λ> :set -package syb
λ> import Data.Generics.Text
λ> data Triple = Triple Text Text Int deriving (Data)
λ> gmapQ gshow (Triple "a" "b" 1821)
["(pack \"a\")","(pack \"b\")","(1821)"]
I'll warn you though: not knowing which type you want in advance severely limits what you can do with generics. Not everything can be stringified and even when they are it's ugly (as seen above). Even knowing a whitelist of what types you want will aid you substantially:
λ> import Control.Arrow
λ> :set -XScopedTypeVariables
λ> let show' (proxy :: Proxy a) = Kleisli (\x -> show <$> (cast x :: Maybe a))
λ> gmapQ (runKleisli (show' (Proxy :: Proxy Int) <+> show' (Proxy :: Proxy Text))) (Triple "a" "b" 1821)
["a","b","1821"]
Note: getValuesOfDataValue doesn't have to return exactly a [String] type, it just need to have the values packed in something.
The question is what to pack it in. The way gshow works is that it recursively calls gmapQ (and its helper extQ, which is built from gmapQ and cast) on the Data a => a value:
-- | Generic show: an alternative to \"deriving Show\"
gshow :: Data a => a -> String
gshow x = gshows x ""
-- | Generic shows
gshows :: Data a => a -> ShowS
-- This is a prefix-show using surrounding "(" and ")",
-- where we recurse into subterms with gmapQ.
gshows = ( \t ->
showChar '('
. (showString . showConstr . toConstr $ t)
. (foldr (.) id . gmapQ ((showChar ' ' .) . gshows) $ t)
. showChar ')'
) `extQ` (shows :: String -> ShowS)
It has a base case of String -> ShowS so whenever it hits a string it knows to return it and terminate. Without knowing more details about your problem domain, I would say to you to go out and build your own gshows using the same strategy. In the very general case where you want to pack every type, there can be no answer, but perhaps something specific exists for your particular task.

Resources