types-compat-0.1.1: ghc-7.6/7.8 compatible GHC.TypeLits, Data.Typeable and Data.Proxy.

Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Typeable.Compat

Synopsis

Documentation

class Typeable a

The class Typeable allows a concrete representation of a type to be calculated.

Minimal complete definition

typeRep#

Instances

Typeable * Bool 
Typeable * Char 
Typeable * Double 
Typeable * Float 
Typeable * Int 
Typeable * Integer 
Typeable * Ordering 
Typeable * RealWorld 
Typeable * Word 
Typeable * Word8 
Typeable * Word16 
Typeable * Word32 
Typeable * Word64 
Typeable * () 
Typeable * TypeRep 
Typeable * TyCon 
(Typeable (k1 -> k) s, Typeable k1 a) => Typeable k (s a)

Kind-polymorphic Typeable instance for type application

Typeable ((* -> *) -> Constraint) Alternative 
Typeable ((* -> *) -> Constraint) Applicative 
Typeable (* -> * -> * -> * -> * -> * -> * -> *) (,,,,,,) 
Typeable (* -> * -> * -> * -> * -> * -> *) (,,,,,) 
Typeable (* -> * -> * -> * -> * -> *) (,,,,) 
Typeable (* -> * -> * -> * -> *) (,,,) 
Typeable (* -> * -> * -> *) (,,) 
Typeable (* -> * -> * -> *) STArray 
Typeable (* -> * -> *) (->) 
Typeable (* -> * -> *) Either 
Typeable (* -> * -> *) (,) 
Typeable (* -> * -> *) Array 
Typeable (* -> * -> *) STRef 
Typeable (* -> * -> *) ST 
Typeable (* -> *) [] 
Typeable (* -> *) Ratio 
Typeable (* -> *) IO 
Typeable (* -> *) Ptr 
Typeable (* -> *) FunPtr 
Typeable (* -> *) Maybe 
Typeable (* -> Constraint) Monoid 
Typeable (k -> *) (Proxy k) 
Typeable (k -> k -> *) (Coercion k) 
Typeable (k -> k -> *) ((:~:) k) 

typeOf :: Typeable * a => a -> TypeRep

cast :: (Typeable * a, Typeable * b) => a -> Maybe b

The type-safe cast operation

gcast :: (Typeable k a, Typeable k b) => c a -> Maybe (c b)

A flexible variation parameterised in a type constructor

data TypeRep :: *

A concrete representation of a (monomorphic) type. TypeRep supports reasonably efficient equality.

data TyCon :: *

An abstract representation of a type constructor. TyCon objects can be built using mkTyCon.

tyConString :: TyCon -> String

Observe string encoding of a type representation

tyConPackage :: TyCon -> String

Since: 4.5.0.0

tyConModule :: TyCon -> String

Since: 4.5.0.0

tyConName :: TyCon -> String

Since: 4.5.0.0

mkTyCon3

Arguments

:: String

package name

-> String

module name

-> String

the name of the type constructor

-> TyCon

A unique TyCon object

Builds a TyCon object representing a type constructor. An implementation of Data.Typeable should ensure that the following holds:

 A==A' ^ B==B' ^ C==C' ==> mkTyCon A B C == mkTyCon A' B' C'

mkTyConApp :: TyCon -> [TypeRep] -> TypeRep

Applies a type constructor to a sequence of types

mkAppTy :: TypeRep -> TypeRep -> TypeRep

Adds a TypeRep argument to a TypeRep.

mkFunTy :: TypeRep -> TypeRep -> TypeRep

A special case of mkTyConApp, which applies the function type constructor to a pair of types.

splitTyConApp :: TypeRep -> (TyCon, [TypeRep])

Splits a type constructor application

funResultTy :: TypeRep -> TypeRep -> Maybe TypeRep

Applies a type to a function type. Returns: Just u if the first argument represents a function of type t -> u and the second argument represents a function of type t. Otherwise, returns Nothing.

typeRepTyCon :: TypeRep -> TyCon

Observe the type constructor of a type representation

typeRepArgs :: TypeRep -> [TypeRep]

Observe the argument types of a type representation

typeRep :: Typeable k a => proxy a -> TypeRep

Takes a value of type a and returns a concrete representation of that type.

Since: 4.7.0.0

data Proxy t :: k -> *

A concrete, poly-kinded proxy type

Constructors

Proxy 

Instances

Monad (Proxy *) 
Functor (Proxy *) 
Applicative (Proxy *) 
Bounded (Proxy k s) 
Enum (Proxy k s) 
Eq (Proxy k s) 
Ord (Proxy k s) 
Read (Proxy k s) 
Show (Proxy k s) 
Ix (Proxy k s) 
Generic (Proxy * t) 
Monoid (Proxy * s) 
Typeable (k -> *) (Proxy k) 
type Rep (Proxy k t) = D1 D1Proxy (C1 C1_0Proxy U1)