[Template-haskell] reifyType function
Andre Pang
ozone@algorithm.com.au
Mon, 7 Jul 2003 18:54:45 +1000
Hi all,
Sean Seefried and I managed to implement a reifyType function, which
we're calling rType since there's already that annoying built-in
reifyType identifier ;). It's defined in a ReifyType module which
looks like thus:
--8<--
module ReifyType
where
import Data.Dynamic
import Language.Haskell.THSyntax
class ReifyType a where
rType :: a -> Typ
instance (ReifyType a, ReifyType b) => ReifyType (a, b) where
rType (_ :: (t, u)) = Tapp (Tapp (Tcon (Tuple 2)) (rType (undefined
:: t)))
(rType (undefined :: u))
instance ReifyType a => ReifyType [a] where
rType (_ :: [t]) = Tapp (Tcon List) (rType (undefined :: t))
instance Typeable a => ReifyType a where
rType (_ :: t) = (Tcon (TconName typeAsString))
where
typeAsString = show $ typeOf (undefined :: t)
instance (ReifyType a, ReifyType b) => ReifyType (a->b) where
rType (_ :: t -> u)
= (Tapp (rType (undefined :: t)) (rType (undefined :: u)))
--8<--
An example of how to use it:
18:48 ~/Desktop % ghci -fglasgow-exts -fallow-overlapping-instances
-fallow-undecidable-instances ReifyType.hs
Type.hs)
...
Loading package base ... linking ... done.
Compiling ReifyType ( ReifyType.hs, interpreted )
Ok, modules loaded: ReifyType.
*ReifyType> rType Char.toLower
Loading package haskell98 ... linking ... done.
Loading package haskell-src ... linking ... done.
Tapp (Tcon (TconName "Char")) (Tcon (TconName "Char"))
*ReifyType> rType ((+) :: (Int -> Int -> Int))
Tapp (Tcon (TconName "Int")) (Tapp (Tcon (TconName "Int")) (Tcon
(TconName "Int")))
*ReifyType> rType "foobar"
Tapp (Tcon List) (Tcon (TconName "Char"))
*ReifyType>
The major restriction is that you're limited to using it on monomorphic
types (since the typeOf function only works on monomorphic types), but
otherwise, it seems to work remarkably well.
--
% Andre Pang : just.your.average.bounty.hunter