| License | BSD-style (see the LICENSE file in the distribution) | 
|---|---|
| Maintainer | libraries@haskell.org | 
| Stability | experimental | 
| Portability | portable | 
| Safe Haskell | Trustworthy | 
| Language | Haskell2010 | 
Data.Proxy
Description
Definition of a Proxy type (poly-kinded in GHC)
Since: base-4.7.0.0
Documentation
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 aundefined :: a
>>>Proxy :: Proxy (Void, Int -> Int)Proxy
Proxy can even hold types of higher kinds,
>>>Proxy :: Proxy EitherProxy
>>>Proxy :: Proxy FunctorProxy
>>>Proxy :: Proxy complicatedStructureProxy
Constructors
| Proxy | 
Instances
| Generic1 (Proxy :: k -> Type) Source # | |
| MonadZip (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 | 
| Foldable (Proxy :: TYPE LiftedRep -> Type) Source # | Since: base-4.7.0.0 | 
| Defined in 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 # | |
| Eq1 (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 | 
| Ord1 (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 | 
| Defined in Data.Functor.Classes | |
| Read1 (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 | 
| Defined in Data.Functor.Classes Methods liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Proxy a) Source # liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Proxy a] Source # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Proxy a) Source # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Proxy a] Source # | |
| Show1 (Proxy :: TYPE LiftedRep -> Type) Source # | Since: base-4.9.0.0 | 
| Contravariant (Proxy :: Type -> Type) Source # | |
| Traversable (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 | 
| Alternative (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 | 
| Applicative (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 | 
| Functor (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 | 
| Monad (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 | 
| MonadPlus (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 | 
| Data t => Data (Proxy t) Source # | Since: base-4.7.0.0 | 
| Defined in 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 # | |
| Monoid (Proxy s) Source # | Since: base-4.7.0.0 | 
| Semigroup (Proxy s) Source # | Since: base-4.9.0.0 | 
| Bounded (Proxy t) Source # | Since: base-4.7.0.0 | 
| Enum (Proxy s) Source # | Since: base-4.7.0.0 | 
| Defined in 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) Source # | |
| Ix (Proxy s) Source # | Since: base-4.7.0.0 | 
| Read (Proxy t) Source # | Since: base-4.7.0.0 | 
| Show (Proxy s) Source # | Since: base-4.7.0.0 | 
| Eq (Proxy s) Source # | Since: base-4.7.0.0 | 
| Ord (Proxy s) Source # | Since: base-4.7.0.0 | 
| type Rep1 (Proxy :: k -> Type) Source # | Since: base-4.6.0.0 | 
| type Rep (Proxy t) Source # | Since: base-4.6.0.0 | 
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 Data.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 Data.Word>>>:type asProxyTypeOf 123 (Just (undefined :: Word8))asProxyTypeOf 123 (Just (undefined :: Word8)) :: Word8