base-4.9.1.0: Basic libraries

Copyright(c) The University of Glasgow CWI 2001--2011
LicenseBSD-style (see the file libraries/base/LICENSE)
Safe HaskellTrustworthy
LanguageHaskell2010

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.

Synopsis

Documentation

data Proxy t Source #

A concrete, poly-kinded proxy type

Constructors

Proxy 

Instances

Monad (Proxy *) # 

Methods

(>>=) :: Proxy * a -> (a -> Proxy * b) -> Proxy * b Source #

(>>) :: Proxy * a -> Proxy * b -> Proxy * b Source #

return :: a -> Proxy * a Source #

fail :: String -> Proxy * a Source #

Functor (Proxy *) # 

Methods

fmap :: (a -> b) -> Proxy * a -> Proxy * b Source #

(<$) :: a -> Proxy * b -> Proxy * a Source #

Applicative (Proxy *) # 

Methods

pure :: a -> Proxy * a Source #

(<*>) :: Proxy * (a -> b) -> Proxy * a -> Proxy * b Source #

(*>) :: Proxy * a -> Proxy * b -> Proxy * b Source #

(<*) :: Proxy * a -> Proxy * b -> Proxy * a Source #

Foldable (Proxy *) # 

Methods

fold :: Monoid m => Proxy * m -> m Source #

foldMap :: Monoid m => (a -> m) -> Proxy * a -> m Source #

foldr :: (a -> b -> b) -> b -> Proxy * a -> b Source #

foldr' :: (a -> b -> b) -> b -> Proxy * a -> b Source #

foldl :: (b -> a -> b) -> b -> Proxy * a -> b Source #

foldl' :: (b -> a -> b) -> b -> Proxy * a -> b Source #

foldr1 :: (a -> a -> a) -> Proxy * a -> a Source #

foldl1 :: (a -> a -> a) -> Proxy * a -> a Source #

toList :: Proxy * a -> [a] Source #

null :: Proxy * a -> Bool Source #

length :: Proxy * a -> Int Source #

elem :: Eq a => a -> Proxy * a -> Bool Source #

maximum :: Ord a => Proxy * a -> a Source #

minimum :: Ord a => Proxy * a -> a Source #

sum :: Num a => Proxy * a -> a Source #

product :: Num a => Proxy * a -> a Source #

Traversable (Proxy *) # 

Methods

traverse :: Applicative f => (a -> f b) -> Proxy * a -> f (Proxy * b) Source #

sequenceA :: Applicative f => Proxy * (f a) -> f (Proxy * a) Source #

mapM :: Monad m => (a -> m b) -> Proxy * a -> m (Proxy * b) Source #

sequence :: Monad m => Proxy * (m a) -> m (Proxy * a) Source #

Generic1 (Proxy *) # 

Associated Types

type Rep1 (Proxy * :: * -> *) :: * -> * Source #

Methods

from1 :: Proxy * a -> Rep1 (Proxy *) a Source #

to1 :: Rep1 (Proxy *) a -> Proxy * a Source #

MonadPlus (Proxy *) # 

Methods

mzero :: Proxy * a Source #

mplus :: Proxy * a -> Proxy * a -> Proxy * a Source #

Alternative (Proxy *) # 

Methods

empty :: Proxy * a Source #

(<|>) :: Proxy * a -> Proxy * a -> Proxy * a Source #

some :: Proxy * a -> Proxy * [a] Source #

many :: Proxy * a -> Proxy * [a] Source #

MonadZip (Proxy *) # 

Methods

mzip :: Proxy * a -> Proxy * b -> Proxy * (a, b) Source #

mzipWith :: (a -> b -> c) -> Proxy * a -> Proxy * b -> Proxy * c Source #

munzip :: Proxy * (a, b) -> (Proxy * a, Proxy * b) Source #

Show1 (Proxy *) #

Since: 4.9.0.0

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Proxy * a -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Proxy * a] -> ShowS Source #

Read1 (Proxy *) #

Since: 4.9.0.0

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Proxy * a) Source #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Proxy * a] Source #

Ord1 (Proxy *) #

Since: 4.9.0.0

Methods

liftCompare :: (a -> b -> Ordering) -> Proxy * a -> Proxy * b -> Ordering Source #

Eq1 (Proxy *) #

Since: 4.9.0.0

Methods

liftEq :: (a -> b -> Bool) -> Proxy * a -> Proxy * b -> Bool Source #

Bounded (Proxy k s) # 

Methods

minBound :: Proxy k s Source #

maxBound :: Proxy k s Source #

Enum (Proxy k s) # 

Methods

succ :: Proxy k s -> Proxy k s Source #

pred :: Proxy k s -> Proxy k s Source #

toEnum :: Int -> Proxy k s Source #

fromEnum :: Proxy k s -> Int Source #

enumFrom :: Proxy k s -> [Proxy k s] Source #

enumFromThen :: Proxy k s -> Proxy k s -> [Proxy k s] Source #

enumFromTo :: Proxy k s -> Proxy k s -> [Proxy k s] Source #

enumFromThenTo :: Proxy k s -> Proxy k s -> Proxy k s -> [Proxy k s] Source #

Eq (Proxy k s) # 

Methods

(==) :: Proxy k s -> Proxy k s -> Bool Source #

(/=) :: Proxy k s -> Proxy k s -> Bool Source #

Data t => Data (Proxy * t) # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Proxy * t -> c (Proxy * t) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Proxy * t) Source #

toConstr :: Proxy * t -> Constr Source #

dataTypeOf :: Proxy * t -> DataType Source #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Proxy * t)) Source #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Proxy * t)) Source #

gmapT :: (forall b. Data b => b -> b) -> Proxy * t -> Proxy * t Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Proxy * t -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Proxy * t -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Proxy * t -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Proxy * t -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Proxy * t -> m (Proxy * t) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy * t -> m (Proxy * t) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy * t -> m (Proxy * t) Source #

Ord (Proxy k s) # 

Methods

compare :: Proxy k s -> Proxy k s -> Ordering Source #

(<) :: Proxy k s -> Proxy k s -> Bool Source #

(<=) :: Proxy k s -> Proxy k s -> Bool Source #

(>) :: Proxy k s -> Proxy k s -> Bool Source #

(>=) :: Proxy k s -> Proxy k s -> Bool Source #

max :: Proxy k s -> Proxy k s -> Proxy k s Source #

min :: Proxy k s -> Proxy k s -> Proxy k s Source #

Read (Proxy k s) # 
Show (Proxy k s) # 

Methods

showsPrec :: Int -> Proxy k s -> ShowS Source #

show :: Proxy k s -> String Source #

showList :: [Proxy k s] -> ShowS Source #

Ix (Proxy k s) # 

Methods

range :: (Proxy k s, Proxy k s) -> [Proxy k s] Source #

index :: (Proxy k s, Proxy k s) -> Proxy k s -> Int Source #

unsafeIndex :: (Proxy k s, Proxy k s) -> Proxy k s -> Int

inRange :: (Proxy k s, Proxy k s) -> Proxy k s -> Bool Source #

rangeSize :: (Proxy k s, Proxy k s) -> Int Source #

unsafeRangeSize :: (Proxy k s, Proxy k s) -> Int

Generic (Proxy k t) # 

Associated Types

type Rep (Proxy k t) :: * -> * Source #

Methods

from :: Proxy k t -> Rep (Proxy k t) x Source #

to :: Rep (Proxy k t) x -> Proxy k t Source #

Semigroup (Proxy k s) # 

Methods

(<>) :: Proxy k s -> Proxy k s -> Proxy k s Source #

sconcat :: NonEmpty (Proxy k s) -> Proxy k s Source #

stimes :: Integral b => b -> Proxy k s -> Proxy k s Source #

Monoid (Proxy k s) # 

Methods

mempty :: Proxy k s Source #

mappend :: Proxy k s -> Proxy k s -> Proxy k s Source #

mconcat :: [Proxy k s] -> Proxy k s Source #

type Rep1 (Proxy *) # 
type Rep1 (Proxy *) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) U1)
type Rep (Proxy k t) # 
type Rep (Proxy k t) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) U1)

Typeable class

typeOf :: forall a. Typeable a => a -> TypeRep Source #

typeOf1 :: forall t a. Typeable t => t a -> TypeRep Source #

typeOf2 :: forall t a b. Typeable t => t a b -> TypeRep Source #

typeOf3 :: forall t a b c. Typeable t => t a b c -> TypeRep Source #

typeOf4 :: forall t a b c d. Typeable t => t a b c d -> TypeRep Source #

typeOf5 :: forall t a b c d e. Typeable t => t a b c d e -> TypeRep Source #

typeOf6 :: forall t a b c d e f. Typeable t => t a b c d e f -> TypeRep Source #

typeOf7 :: forall t a b c d e f g. Typeable t => t a b c d e f g -> TypeRep Source #

type Typeable1 a = Typeable a Source #

Deprecated: renamed to Typeable

type Typeable2 a = Typeable a Source #

Deprecated: renamed to Typeable

type Typeable3 a = Typeable a Source #

Deprecated: renamed to Typeable

type Typeable4 a = Typeable a Source #

Deprecated: renamed to Typeable

type Typeable5 a = Typeable a Source #

Deprecated: renamed to Typeable

type Typeable6 a = Typeable a Source #

Deprecated: renamed to Typeable

type Typeable7 a = Typeable a Source #

Deprecated: renamed to Typeable

Module

TyCon

tyConString :: TyCon -> String Source #

Deprecated: renamed to tyConName; tyConModule and tyConPackage are also available.

Observe string encoding of a type representation

mkTyCon3 Source #

Arguments

:: String

package name

-> String

module name

-> String

the name of the type constructor

-> TyCon

A unique TyCon object Used when the strings are dynamically allocated, eg from binary deserialisation

mkTyCon3# Source #

Arguments

:: Addr#

package name

-> Addr#

module name

-> Addr#

the name of the type constructor

-> TyCon

A unique TyCon object

TypeRep

data TypeRep Source #

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

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

mkAppTy :: TypeRep -> TypeRep -> TypeRep Source #

Adds a TypeRep argument to a TypeRep.

typeRepTyCon :: TypeRep -> TyCon Source #

Observe the type constructor of a type representation

class Typeable a where Source #

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

Minimal complete definition

typeRep#

Methods

typeRep# :: Proxy# a -> TypeRep Source #

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 constructor 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

funResultTy :: TypeRep -> TypeRep -> Maybe TypeRep Source #

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.

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

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

typeNatTypeRep :: KnownNat a => Proxy# a -> TypeRep Source #

Used to make `Typeable instance for things of kind Nat