{-# LANGUAGE BangPatterns #-}
module Data.Rank1Typeable
(
TypeRep
, typeOf
, splitTyConApp
, mkTyConApp
, isInstanceOf
, funResultTy
, TypeError
, TypVar
, Zero
, Succ
, V0
, V1
, V2
, V3
, V4
, V5
, V6
, V7
, V8
, V9
, ANY
, ANY1
, ANY2
, ANY3
, ANY4
, ANY5
, ANY6
, ANY7
, ANY8
, ANY9
, Typeable
) where
import Prelude hiding (succ)
import Control.Arrow ((***), second)
import Control.Monad (void)
import Control.Applicative ((<$>))
import Data.Binary
import Data.Function (on)
import Data.List (intersperse, isPrefixOf)
import Data.Maybe (fromMaybe)
import Data.Typeable ( Typeable )
import qualified Data.Typeable as T
import GHC.Fingerprint
tcList, tcFun :: TyCon
tcList = fst $ splitTyConApp $ typeOf [()]
tcFun = fst $ splitTyConApp $ typeOf (\() -> ())
data TypeRep
= TRCon TyCon
| TRApp {-# UNPACK #-} !Fingerprint TypeRep TypeRep
data TyCon = TyCon
{ tyConFingerprint :: {-# UNPACK #-} !Fingerprint
, tyConPackage :: String
, tyConModule :: String
, tyConName :: String
}
typeRepFingerprint :: TypeRep -> Fingerprint
typeRepFingerprint (TRCon c) = tyConFingerprint c
typeRepFingerprint (TRApp fp _ _) = fp
instance Eq TyCon where
(==) = (==) `on` tyConFingerprint
instance Eq TypeRep where
(==) = (==) `on` typeRepFingerprint
instance Binary TypeRep where
put (splitTyConApp -> (tc, ts)) = do
put $ tyConPackage tc
put $ tyConModule tc
put $ tyConName tc
put ts
get = do
package <- get
modul <- get
name <- get
ts <- get
return $ mkTyConApp (mkTyCon3 package modul name) ts
typeOf :: Typeable a => a -> TypeRep
typeOf = trTypeOf . T.typeOf
trTypeOf :: T.TypeRep -> TypeRep
trTypeOf t = let (c, ts) = T.splitTyConApp t
in foldl mkTRApp (TRCon $ fromTypeableTyCon c) $ map trTypeOf ts
where
fromTypeableTyCon c =
TyCon (T.tyConFingerprint c)
(T.tyConPackage c)
(T.tyConModule c)
(T.tyConName c)
mkTRApp :: TypeRep -> TypeRep -> TypeRep
mkTRApp t0 t1 = TRApp fp t0 t1
where
fp = fingerprintFingerprints [typeRepFingerprint t0, typeRepFingerprint t1]
mkTyCon3 :: String -> String -> String -> TyCon
mkTyCon3 pkg m name = TyCon fp pkg m name
where
fp = fingerprintFingerprints [ fingerprintString s | s <- [pkg, m, name] ]
splitTyConApp :: TypeRep -> (TyCon, [TypeRep])
splitTyConApp = go []
where
go xs (TRCon c) = (c, xs)
go xs (TRApp _ t0 t1) = go (t1 : xs) t0
mkTyConApp :: TyCon -> [TypeRep] -> TypeRep
mkTyConApp c = foldl mkTRApp (TRCon c)
isTypVar :: TypeRep -> Maybe Var
isTypVar (splitTyConApp -> (c, [t])) | c == typVar = Just t
isTypVar _ = Nothing
mkTypVar :: Var -> TypeRep
mkTypVar x = mkTyConApp typVar [x]
typVar :: TyCon
typVar = let (c, _) = splitTyConApp (typeOf (undefined :: TypVar V0)) in c
skolem :: TyCon
skolem = let (c, _) = splitTyConApp (typeOf (undefined :: Skolem V0)) in c
data TypVar a deriving Typeable
data Skolem a deriving Typeable
data Zero deriving Typeable
data Succ a deriving Typeable
type V0 = Zero
type V1 = Succ V0
type V2 = Succ V1
type V3 = Succ V2
type V4 = Succ V3
type V5 = Succ V4
type V6 = Succ V5
type V7 = Succ V6
type V8 = Succ V7
type V9 = Succ V8
type ANY = TypVar V0
type ANY1 = TypVar V1
type ANY2 = TypVar V2
type ANY3 = TypVar V3
type ANY4 = TypVar V4
type ANY5 = TypVar V5
type ANY6 = TypVar V6
type ANY7 = TypVar V7
type ANY8 = TypVar V8
type ANY9 = TypVar V9
type TypeError = String
isInstanceOf :: TypeRep -> TypeRep -> Either TypeError ()
isInstanceOf t1 t2 = void (unify (skolemize t1) t2)
funResultTy :: TypeRep -> TypeRep -> Either TypeError TypeRep
funResultTy t1 t2 = do
let anyTy = mkTypVar $ typeOf (undefined :: V0)
s <- unify (alphaRename "f" t1) $ mkTyConApp tcFun [alphaRename "x" t2, anyTy]
return $ normalize $ subst s anyTy
alphaRename :: String -> TypeRep -> TypeRep
alphaRename prefix (isTypVar -> Just x) =
mkTypVar (mkTyConApp (mkTyCon prefix) [x])
alphaRename prefix (splitTyConApp -> (c, ts)) =
mkTyConApp c (map (alphaRename prefix) ts)
tvars :: TypeRep -> [Var]
tvars (isTypVar -> Just x) = [x]
tvars (splitTyConApp -> (_, ts)) = concatMap tvars ts
normalize :: TypeRep -> TypeRep
normalize t = subst (zip (tvars t) anys) t
where
anys :: [TypeRep]
anys = map mkTypVar (iterate succ zero)
succ :: TypeRep -> TypeRep
succ = mkTyConApp succTyCon . (:[])
zero :: TypeRep
zero = mkTyConApp zeroTyCon []
mkTyCon :: String -> TyCon
mkTyCon = mkTyCon3 "rank1typeable" "Data.Rank1Typeable"
succTyCon :: TyCon
succTyCon = let (c, _) = splitTyConApp (typeOf (undefined :: Succ Zero)) in c
zeroTyCon :: TyCon
zeroTyCon = let (c, _) = splitTyConApp (typeOf (undefined :: Zero)) in c
type Substitution = [(Var, TypeRep)]
type Equation = (TypeRep, TypeRep)
type Var = TypeRep
skolemize :: TypeRep -> TypeRep
skolemize (isTypVar -> Just x) = mkTyConApp skolem [x]
skolemize (splitTyConApp -> (c, ts)) = mkTyConApp c (map skolemize ts)
occurs :: Var -> TypeRep -> Bool
occurs x (isTypVar -> Just x') = x == x'
occurs x (splitTyConApp -> (_, ts)) = any (occurs x) ts
subst :: Substitution -> TypeRep -> TypeRep
subst s (isTypVar -> Just x) = fromMaybe (mkTypVar x) (lookup x s)
subst s (splitTyConApp -> (c, ts)) = mkTyConApp c (map (subst s) ts)
unify :: TypeRep
-> TypeRep
-> Either TypeError Substitution
unify = \t1 t2 -> go [] [(t1, t2)]
where
go :: Substitution
-> [Equation]
-> Either TypeError Substitution
go acc [] =
return acc
go acc ((t1, t2) : eqs) | t1 == t2 =
go acc eqs
go acc ((isTypVar -> Just x, t) : eqs) =
if x `occurs` t
then Left "Occurs check"
else go ((x, t) : map (second $ subst [(x, t)]) acc)
(map (subst [(x, t)] *** subst [(x, t)]) eqs)
go acc ((t, isTypVar -> Just x) : eqs) =
go acc ((mkTypVar x, t) : eqs)
go acc ((splitTyConApp -> (c1, ts1), splitTyConApp -> (c2, ts2)) : eqs) =
if c1 /= c2
then Left $ "Cannot unify " ++ show c1 ++ " and " ++ show c2
else go acc (zip ts1 ts2 ++ eqs)
instance Show TyCon where
showsPrec _ c = showString (tyConName c)
instance Show TypeRep where
showsPrec p (splitTyConApp -> (tycon, tys)) =
case tys of
[] -> showsPrec p tycon
[anyIdx -> Just i] | tycon == typVar -> showString "ANY" . showIdx i
[x] | tycon == tcList ->
showChar '[' . shows x . showChar ']'
[a,r] | tycon == tcFun ->
showParen (p > 8) $ showsPrec 9 a
. showString " -> "
. showsPrec 8 r
xs | isTupleTyCon tycon ->
showTuple xs
_ ->
showParen (p > 9) $ showsPrec p tycon
. showChar ' '
. showArgs tys
where
showIdx 0 = showString ""
showIdx i = shows i
showArgs :: Show a => [a] -> ShowS
showArgs [] = id
showArgs [a] = showsPrec 10 a
showArgs (a:as) = showsPrec 10 a . showString " " . showArgs as
anyIdx :: TypeRep -> Maybe Int
anyIdx (splitTyConApp -> (c, [])) | c == zeroTyCon = Just 0
anyIdx (splitTyConApp -> (c, [t])) | c == succTyCon = (+1) <$> anyIdx t
anyIdx _ = Nothing
showTuple :: [TypeRep] -> ShowS
showTuple args = showChar '('
. foldr (.) id ( intersperse (showChar ',')
$ map (showsPrec 10) args
)
. showChar ')'
isTupleTyCon :: TyCon -> Bool
isTupleTyCon = isPrefixOf "(," . tyConName