base-4.20.0.0: Core data structures and operations
LicenseBSD-style (see the LICENSE file in the distribution)
Maintainerlibraries@haskell.org
Stabilitystable
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Data.Proxy

Description

Definition of a Proxy type (poly-kinded in GHC)

Since: base-4.7.0.0

Synopsis

Documentation

data Proxy (t :: k) Source #

Proxy is a type that holds no data, but has a phantom parameter of arbitrary type (or even kind). Its use is to provide type information, even though there is no value available of that type (or it may be too costly to create one).

Historically, Proxy :: Proxy a is a safer alternative to the undefined :: a idiom.

>>> Proxy :: Proxy (Void, Int -> Int)
Proxy

Proxy can even hold types of higher kinds,

>>> Proxy :: Proxy Either
Proxy
>>> Proxy :: Proxy Functor
Proxy
>>> Proxy :: Proxy complicatedStructure
Proxy

Constructors

Proxy 

Instances

Instances details
Generic1 (Proxy :: k -> Type) 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 (Proxy :: k -> Type)

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (Proxy :: k -> Type) = D1 ('MetaData "Proxy" "GHC.Internal.Data.Proxy" "ghc-internal" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: k -> Type))

Methods

from1 :: forall (a :: k). Proxy a -> Rep1 (Proxy :: k -> Type) a Source #

to1 :: forall (a :: k). Rep1 (Proxy :: k -> Type) a -> Proxy a Source #

MonadZip (Proxy :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Zip

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 #

Eq1 (Proxy :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Ord1 (Proxy :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Read1 (Proxy :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Show1 (Proxy :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

Contravariant (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Proxy a -> Proxy a' Source #

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

Alternative (Proxy :: Type -> Type)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.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 #

Applicative (Proxy :: Type -> Type)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

pure :: a -> Proxy a Source #

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

liftA2 :: (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c Source #

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

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

Functor (Proxy :: Type -> Type)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

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

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

Monad (Proxy :: Type -> Type)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

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

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

return :: a -> Proxy a Source #

MonadPlus (Proxy :: Type -> Type)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

mzero :: Proxy a Source #

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

Foldable (Proxy :: Type -> Type)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Foldable

Methods

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

foldMap :: Monoid m => (a -> m) -> Proxy a -> 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 :: Type -> Type)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

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 #

Monoid (Proxy s)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

mempty :: Proxy s Source #

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

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

Semigroup (Proxy s)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

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

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

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

Data t => Data (Proxy t)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Data

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 t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Proxy t)) Source #

dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 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 :: forall r r'. (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 #

Bounded (Proxy t)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Enum (Proxy s)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

succ :: Proxy s -> Proxy s Source #

pred :: Proxy s -> Proxy s Source #

toEnum :: Int -> Proxy s Source #

fromEnum :: Proxy s -> Int Source #

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

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

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

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

Generic (Proxy t) 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep (Proxy t)

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep (Proxy t) = D1 ('MetaData "Proxy" "GHC.Internal.Data.Proxy" "ghc-internal" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

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

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

Ix (Proxy s)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

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

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

unsafeIndex :: (Proxy s, Proxy s) -> Proxy s -> Int Source #

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

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

unsafeRangeSize :: (Proxy s, Proxy s) -> Int Source #

Read (Proxy t)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Show (Proxy s)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Eq (Proxy s)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

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

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

Ord (Proxy s)

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

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

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

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

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

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

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

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

type Rep1 (Proxy :: k -> Type)

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (Proxy :: k -> Type) = D1 ('MetaData "Proxy" "GHC.Internal.Data.Proxy" "ghc-internal" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: k -> Type))
type Rep (Proxy t)

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep (Proxy t) = D1 ('MetaData "Proxy" "GHC.Internal.Data.Proxy" "ghc-internal" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: Type -> Type))

asProxyTypeOf :: a -> proxy a -> a Source #

asProxyTypeOf is a type-restricted version of const. It is usually used as an infix operator, and its typing forces its first argument (which is usually overloaded) to have the same type as the tag of the second.

>>> import GHC.Internal.Word
>>> :type asProxyTypeOf 123 (Proxy :: Proxy Word8)
asProxyTypeOf 123 (Proxy :: Proxy Word8) :: Word8

Note the lower-case proxy in the definition. This allows any type constructor with just one argument to be passed to the function, for example we could also write

>>> import GHC.Internal.Word
>>> :type asProxyTypeOf 123 (Just (undefined :: Word8))
asProxyTypeOf 123 (Just (undefined :: Word8)) :: Word8

data KProxy t Source #

A concrete, promotable proxy type, for use at the kind level. There are no instances for this because it is intended at the kind level only

Constructors

KProxy