Copyright | (c) The University of Glasgow, CWI 2001--2011 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Safe Haskell | Unsafe |
Language | Haskell2010 |
The representations of the types TyCon and TypeRep, and the function mkTyCon which is used by derived instances of Typeable to construct a TyCon.
- data Proxy t = Proxy
- data TypeRep = TypeRep !Fingerprint TyCon [TypeRep]
- data Fingerprint = Fingerprint !Word64 !Word64
- typeOf :: forall a. Typeable a => a -> TypeRep
- typeOf1 :: forall t a. Typeable t => t a -> TypeRep
- typeOf2 :: forall t a b. Typeable t => t a b -> TypeRep
- typeOf3 :: forall t a b c. Typeable t => t a b c -> TypeRep
- typeOf4 :: forall t a b c d. Typeable t => t a b c d -> TypeRep
- typeOf5 :: forall t a b c d e. Typeable t => t a b c d e -> TypeRep
- typeOf6 :: forall t a b c d e f. Typeable t => t a b c d e f -> TypeRep
- typeOf7 :: forall t a b c d e f g. Typeable t => t a b c d e f g -> TypeRep
- type Typeable1 a = Typeable a
- type Typeable2 a = Typeable a
- type Typeable3 a = Typeable a
- type Typeable4 a = Typeable a
- type Typeable5 a = Typeable a
- type Typeable6 a = Typeable a
- type Typeable7 a = Typeable a
- data TyCon = TyCon {}
- typeRep :: forall proxy a. Typeable a => proxy a -> TypeRep
- mkTyCon :: Word# -> Word# -> String -> String -> String -> TyCon
- mkTyCon3 :: String -> String -> String -> TyCon
- mkTyConApp :: TyCon -> [TypeRep] -> TypeRep
- mkAppTy :: TypeRep -> TypeRep -> TypeRep
- typeRepTyCon :: TypeRep -> TyCon
- class Typeable a where
- mkFunTy :: TypeRep -> TypeRep -> TypeRep
- splitTyConApp :: TypeRep -> (TyCon, [TypeRep])
- funResultTy :: TypeRep -> TypeRep -> Maybe TypeRep
- typeRepArgs :: TypeRep -> [TypeRep]
- showsTypeRep :: TypeRep -> ShowS
- tyConString :: TyCon -> String
- listTc :: TyCon
- funTc :: TyCon
Documentation
A concrete, poly-kinded proxy type
Monad (Proxy *) | |
Functor (Proxy *) | |
Applicative (Proxy *) | |
Foldable (Proxy *) | |
Traversable (Proxy *) | |
Bounded (Proxy k s) | |
Enum (Proxy k s) | |
Eq (Proxy k s) | |
Data t => Data (Proxy * t) | |
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) |
A concrete representation of a (monomorphic) type. TypeRep
supports reasonably efficient equality.
data Fingerprint Source
TyCon | |
|
typeRep :: forall proxy a. Typeable a => proxy a -> TypeRep Source
Takes a value of type a
and returns a concrete representation
of that type.
Since: 4.7.0.0
:: String | package name |
-> String | module name |
-> String | the name of the type constructor |
-> TyCon | A unique |
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 Source
Applies a type constructor to a sequence of types
typeRepTyCon :: TypeRep -> TyCon Source
Observe the type constructor of a type representation
The class Typeable
allows a concrete representation of a type to
be calculated.
mkFunTy :: TypeRep -> TypeRep -> TypeRep Source
A special case of mkTyConApp
, which applies the function
type constructor to a pair of types.
splitTyConApp :: TypeRep -> (TyCon, [TypeRep]) Source
Splits a type constructor application
typeRepArgs :: TypeRep -> [TypeRep] Source
Observe the argument types of a type representation
showsTypeRep :: TypeRep -> ShowS Source
tyConString :: TyCon -> String Source
Deprecated: renamed to tyConName
; tyConModule
and tyConPackage
are also available.
Observe string encoding of a type representation