| Copyright | (c) The University of Glasgow, CWI 2001--2011 |
|---|---|
| License | BSD-style (see the file libraries/base/LICENSE) |
| Safe Haskell | Trustworthy |
| Language | Haskell2010 |
Data.Typeable.Internal
Contents
Description
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 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 Module :: TYPE Lifted
- moduleName :: Module -> String
- modulePackage :: Module -> String
- data TyCon :: TYPE Lifted
- tyConPackage :: TyCon -> String
- tyConModule :: TyCon -> String
- tyConName :: TyCon -> String
- tyConString :: TyCon -> String
- tyConFingerprint :: TyCon -> Fingerprint
- mkTyCon3 :: String -> String -> String -> TyCon
- mkTyCon3# :: Addr# -> Addr# -> Addr# -> TyCon
- rnfTyCon :: TyCon -> ()
- data TypeRep = TypeRep !Fingerprint TyCon [KindRep] [TypeRep]
- type KindRep = TypeRep
- typeRep :: forall proxy a. Typeable a => proxy a -> TypeRep
- mkTyConApp :: TyCon -> [TypeRep] -> TypeRep
- mkPolyTyConApp :: TyCon -> [KindRep] -> [TypeRep] -> TypeRep
- mkAppTy :: TypeRep -> TypeRep -> TypeRep
- typeRepTyCon :: TypeRep -> TyCon
- class Typeable a where
- mkFunTy :: TypeRep -> TypeRep -> TypeRep
- splitTyConApp :: TypeRep -> (TyCon, [TypeRep])
- splitPolyTyConApp :: TypeRep -> (TyCon, [KindRep], [TypeRep])
- funResultTy :: TypeRep -> TypeRep -> Maybe TypeRep
- typeRepArgs :: TypeRep -> [TypeRep]
- typeRepFingerprint :: TypeRep -> Fingerprint
- rnfTypeRep :: TypeRep -> ()
- showsTypeRep :: TypeRep -> ShowS
- typeRepKinds :: TypeRep -> [KindRep]
- typeSymbolTypeRep :: KnownSymbol a => Proxy# a -> TypeRep
- typeNatTypeRep :: KnownNat a => Proxy# a -> TypeRep
Documentation
A concrete, poly-kinded proxy type
Constructors
| Proxy |
Instances
| Monad (Proxy (TYPE Lifted)) | |
| Functor (Proxy (TYPE Lifted)) | |
| Applicative (Proxy (TYPE Lifted)) | |
| Foldable (Proxy (TYPE Lifted)) | |
| Traversable (Proxy (TYPE Lifted)) | |
| Generic1 (Proxy *) | |
| Bounded (Proxy k s) | |
| Enum (Proxy k s) | |
| Eq (Proxy k s) | |
| Data t => Data (Proxy (TYPE Lifted) t) | |
| Ord (Proxy k s) | |
| Read (Proxy k s) | |
| Show (Proxy k s) | |
| Ix (Proxy k s) | |
| Generic (Proxy k t) | |
| Semigroup (Proxy k s) | |
| Monoid (Proxy k s) | |
| type Rep1 (Proxy k) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) U1) | |
| type Rep (Proxy k t) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) U1) | |
Typeable class
Module
moduleName :: Module -> String Source
modulePackage :: Module -> String Source
TyCon
tyConPackage :: TyCon -> String Source
tyConModule :: TyCon -> String Source
tyConString :: TyCon -> String Source
Deprecated: renamed to tyConName; tyConModule and tyConPackage are also available.
Observe string encoding of a type representation
TypeRep
A concrete representation of a (monomorphic) type.
TypeRep supports reasonably efficient equality.
Constructors
| TypeRep !Fingerprint TyCon [KindRep] [TypeRep] |
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
mkTyConApp :: TyCon -> [TypeRep] -> TypeRep Source
Applies a kind-monomorphic type constructor to a sequence of types
mkPolyTyConApp :: TyCon -> [KindRep] -> [TypeRep] -> TypeRep Source
Applies a kind-polymorphic type constructor to a sequence of kinds and 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.
Minimal complete definition
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.
Note that if the type construcotr is polymorphic, this will
not return the kinds that were used.
See splitPolyTyConApp if you need all parts.
splitPolyTyConApp :: TypeRep -> (TyCon, [KindRep], [TypeRep]) Source
Split a type constructor application
typeRepArgs :: TypeRep -> [TypeRep] Source
Observe the argument types of a type representation
typeRepFingerprint :: TypeRep -> Fingerprint Source
Observe the Fingerprint of a type representation
Since: 4.8.0.0
rnfTypeRep :: TypeRep -> () Source
Helper to fully evaluate TypeRep for use as NFData(rnf) implementation
Since: 4.8.0.0
showsTypeRep :: TypeRep -> ShowS Source
typeRepKinds :: TypeRep -> [KindRep] Source
Observe the argument kinds of a type representation
typeSymbolTypeRep :: KnownSymbol a => Proxy# a -> TypeRep Source
Used to make `Typeable instance for things of kind Symbol