{-# LANGUAGE CPP, NoImplicitPrelude #-}
#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif
#if MIN_VERSION_base(4,10,0) && !(MIN_VERSION_base(4,18,0))
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
#endif
module Data.Typeable.Compat (
module Base
#if MIN_VERSION_base(4,10,0)
, heqT
#endif
) where
import Data.Typeable as Base
#if MIN_VERSION_base(4,10,0) && !(MIN_VERSION_base(4,18,0))
import Prelude.Compat
import qualified Type.Reflection.Compat as TR
#endif
#if MIN_VERSION_base(4,10,0) && !(MIN_VERSION_base(4,18,0))
heqT :: forall a b. (Typeable a, Typeable b) => Maybe (a :~~: b)
heqT :: forall {k1} {k2} (a :: k1) (b :: k2).
(Typeable a, Typeable b) =>
Maybe (a :~~: b)
heqT = TypeRep a
ta forall k1 k2 (a :: k1) (b :: k2).
TypeRep a -> TypeRep b -> Maybe (a :~~: b)
`TR.eqTypeRep` TypeRep b
tb
where
ta :: TypeRep a
ta = forall {k} (a :: k). Typeable a => TypeRep a
TR.typeRep :: TR.TypeRep a
tb :: TypeRep b
tb = forall {k} (a :: k). Typeable a => TypeRep a
TR.typeRep :: TR.TypeRep b
#endif