module Data.TypeHash(TypeCode, typeCode, convertibleTo, TypeHash, typeHash) where
import Data.Char(isAlpha)
import Control.Monad.State
import Data.Generics
import Data.Digest.Pure.MD5(MD5Digest, md5)
import Data.ByteString.Lazy(pack)
newtype TypeCode = TypeCode Type
deriving (Eq, Ord, Typeable, Data, Show)
typeCode :: (Data a) => a -> TypeCode
typeCode = TypeCode . gType []
newtype TypeHash = TypeHash String
deriving (Eq, Ord, Typeable, Data, Show, Read)
typeHash :: (Data a) => a -> TypeHash
typeHash = TypeHash . show . md5 . pack . map (fromIntegral . fromEnum) . show . gType []
data Type
= Name { typeName :: String }
| Data { typeName :: String, constrs :: [Constructor] }
deriving (Eq, Ord, Show, Typeable, Data)
type Constructor = (String, [Field])
type Field = (String, Type)
gType :: (Data a) => [String] -> a -> Type
gType tns x =
let tn = show $ fullTypeOf x
in case dataTypeRep $ dataTypeOf x of
AlgRep cs | tn `notElem` tns ->
Data { typeName = tn, constrs = map (gConstr (tn:tns) x) cs }
_ -> Name { typeName = tn }
gConstr :: (Data a) => [String] -> a -> Constr -> (String, [Field])
gConstr tns x c = (showConstr c,
zip fs (reverse $ execState (fromConstrM f c `asTypeOf` return x) []))
where fs = constrFields c ++ [ show i | i <- [0::Int ..] ]
f :: forall d . (Data d) => State [Type] d
f = do modify (gType tns (undefined :: d) :); return undefined
fullTypeOf :: (Data a) => a -> TypeRep
fullTypeOf a | not $ isAlpha $ head $ tyConString $ typeRepTyCon $ ta = ta
| otherwise = mkTyConApp (mkTyCon $ dataTypeName $ dataTypeOf a)
(typeRepArgs ta)
where ta = typeOf a
convertibleTo :: TypeCode -> TypeCode -> Bool
convertibleTo (TypeCode t1) (TypeCode t2) = subType [] t1 t2
type TypeNameMap = [(String, String)]
subType :: TypeNameMap -> Type -> Type -> Bool
subType r (Name n1) (Name n2) = maybe (n1 == n2) (== n2) $ lookup n1 r
subType _ (Name {}) (Data {}) = False
subType _ (Data {}) (Name {}) = False
subType r (Data n1 [(_, fs1)]) (Data n2 [(_,fs2)]) = all (subField ((n1, n2):r) fs1) fs2
subType r (Data n1 cs1) (Data n2 cs2) = all (subConstructor ((n1, n2):r) cs2) cs1
subConstructor :: TypeNameMap -> [Constructor] -> Constructor -> Bool
subConstructor r cs2 (n1, fs1) = maybe False (all (subField r fs1)) $ lookup n1 cs2
subField :: TypeNameMap -> [Field] -> Field -> Bool
subField r fs1 (f2, t2) = maybe False (\ t1 -> subType r t1 t2) $ lookup f2 fs1