{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE CPP
, NoImplicitPrelude
, OverlappingInstances
, ScopedTypeVariables
, FlexibleInstances
#-}
{-# OPTIONS_GHC -funbox-strict-fields -fno-warn-warnings-deprecations #-}
module Data.OldTypeable {-# DEPRECATED "Use Data.Typeable instead" #-}
(
Typeable( typeOf ),
cast,
gcast,
TypeRep,
showsTypeRep,
TyCon,
tyConString,
tyConPackage,
tyConModule,
tyConName,
mkTyCon,
mkTyCon3,
mkTyConApp,
mkAppTy,
mkFunTy,
splitTyConApp,
funResultTy,
typeRepTyCon,
typeRepArgs,
typeRepKey,
TypeRepKey,
Typeable1( typeOf1 ),
Typeable2( typeOf2 ),
Typeable3( typeOf3 ),
Typeable4( typeOf4 ),
Typeable5( typeOf5 ),
Typeable6( typeOf6 ),
Typeable7( typeOf7 ),
gcast1,
gcast2,
typeOfDefault,
typeOf1Default,
typeOf2Default,
typeOf3Default,
typeOf4Default,
typeOf5Default,
typeOf6Default
) where
import Data.OldTypeable.Internal hiding (mkTyCon)
import Unsafe.Coerce
import Data.Maybe
import GHC.Base
import GHC.Fingerprint.Type
import GHC.Fingerprint
#include "OldTypeable.h"
{-# DEPRECATED typeRepKey "TypeRep itself is now an instance of Ord" #-}
typeRepKey :: TypeRep -> IO TypeRepKey
typeRepKey (TypeRep f _ _) = return (TypeRepKey f)
newtype TypeRepKey = TypeRepKey Fingerprint
deriving (Eq,Ord)
{-# DEPRECATED mkTyCon "either derive Typeable, or use mkTyCon3 instead" #-}
mkTyCon :: String
-> TyCon
mkTyCon name = TyCon (fingerprintString name) "" "" name
cast :: (Typeable a, Typeable b) => a -> Maybe b
cast x = r
where
r = if typeOf x == typeOf (fromJust r)
then Just $ unsafeCoerce x
else Nothing
gcast :: (Typeable a, Typeable b) => c a -> Maybe (c b)
gcast x = r
where
r = if typeOf (getArg x) == typeOf (getArg (fromJust r))
then Just $ unsafeCoerce x
else Nothing
getArg :: c x -> x
getArg = undefined
gcast1 :: (Typeable1 t, Typeable1 t') => c (t a) -> Maybe (c (t' a))
gcast1 x = r
where
r = if typeOf1 (getArg x) == typeOf1 (getArg (fromJust r))
then Just $ unsafeCoerce x
else Nothing
getArg :: c x -> x
getArg = undefined
gcast2 :: (Typeable2 t, Typeable2 t') => c (t a b) -> Maybe (c (t' a b))
gcast2 x = r
where
r = if typeOf2 (getArg x) == typeOf2 (getArg (fromJust r))
then Just $ unsafeCoerce x
else Nothing
getArg :: c x -> x
getArg = undefined