Reputation: 333
I have a system in haskell that uses Data.Dynamic and Type.Reflection to perform inference and calculations. I would like to be able to print the results.
Printing is easy when the type is supplied e.g
foo :: Dynamic -> String
foo dyn = case tyConName . someTypeRepTyCon . dynTypeRep $ dyn of
"Int" -> show $ fromDyn dyn (0 :: Int)
"Bool" -> show $ fromDyn dyn True
_ -> "no chance"
But if I want to be able to print tuples, I would have to add a new line for each e.g (Int, Bool), (Bool, Int), (Char, Int, Banana) ....
With the addition of more primitives and larger tuples this quickly becomes impractical.
Is there an algorithmic way to generate strings for this dynamic data, specifically for tuples and lists.
Upvotes: 2
Views: 171
Reputation: 153102
I like the main idea of the other answer, but it seems to get where it's going in a fairly roundabout way. Here's how I would style the same idea:
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE GADTs #-}
import Type.Reflection
import Data.Dynamic
showDyn :: Dynamic -> String
showDyn (Dynamic (App (App (eqTypeRep (typeRep @(,)) -> Just HRefl) ta) tb) (va, vb))
= concat [ "DynamicPair("
, showDyn (Dynamic ta va)
, ","
, showDyn (Dynamic tb vb)
, ")"
]
showDyn (Dynamic (eqTypeRep (typeRep @Integer) -> Just HRefl) n) = show n
showDyn (Dynamic tr _) = show tr
That first pattern match is quite a mouthful, but after playing with a few different ways of formatting it I'm convinced that there just is no way to make that look good. You can try it in ghci:
> showDyn (toDyn ((3,4), (True, "hi")))
"DynamicPair(DynamicPair(3,4),DynamicPair(Bool,[Char]))"
Upvotes: 2
Reputation: 116174
I could only manage to obtain this horrible solution.
{-# LANGUAGE GADTs, ScopedTypeVariables, TypeApplications #-}
{-# OPTIONS -Wall #-}
import Type.Reflection
import Data.Dynamic
Here we define the TyCon
for (,)
and Int
. (I'm pretty sure there must be an easier way.)
pairTyCon :: TyCon
pairTyCon = someTypeRepTyCon (someTypeRep [('a','b')])
intTyCon :: TyCon
intTyCon = someTypeRepTyCon (someTypeRep [42 :: Int])
Then we dissect the Dynamic
type. First we check if it is an Int
.
showDynamic :: Dynamic -> String
showDynamic x = case x of
Dynamic tr@(Con k) v | k == intTyCon ->
case eqTypeRep tr (typeRep @ Int) of
Just HRefl -> show (v :: Int)
_ -> error "It really should be an int"
-- to be continued
The above is ugly, since we first pattern match against the TyCon
using ==
instead of pattern matching, which prevents the type refinement of v
into an Int
. So, we still have to resort to eqTypeRep
to perform a second check which we already know has to succeed.
I think it could be made pretty by checking eqTypeRep
in advance, for instance. Or fromDyn
. It does not matter.
What matters is that the pair case below is even more messy, and can not be made pretty in the same way, as far as I can see.
-- continuing from above
Dynamic tr@(App (App t0@(Con k :: TypeRep p)
(t1 :: TypeRep a1))
(t2 :: TypeRep a2)) v | k == pairTyCon ->
withTypeable t0 $
withTypeable t1 $
withTypeable t2 $
case ( eqTypeRep tr (typeRep @(p a1 a2))
, eqTypeRep (typeRep @p) (typeRep @(,))) of
(Just HRefl, Just HRefl) ->
"DynamicPair("
++ showDynamic (Dynamic t1 (fst v))
++ ", "
++ showDynamic (Dynamic t2 (snd v))
++ ")"
_ -> error "It really should be a pair!"
_ -> "Dynamic: not an int, not a pair"
Above we match the TypeRep
so that it represents something of type p a1 a2
. We require that the representation of p
to be pairTyCon
.
As before this does not trigger type refinement, since it is done with ==
instead of pattern matching. We need to perform another explicit match to force p ~ (,)
and another for the final refinement v :: (a1,a2)
. Sigh.
Finally, we can take fst v
and snd v
, turn them into Dynamic
once again, and pair them. Effectively, we turned the original x :: Dynamic
into something like (fst x, snd x)
where both components are Dynamic
. Now we can recurse.
I would really like to avoid the error
s, but I can not see how to do that at the moment.
The redeeming part is that the approach is very general, and can be easily adapted to other type constructors.
Upvotes: 2