{-# LANGUAGE Trustworthy #-}{-# LANGUAGE NoImplicitPrelude #-}{-# LANGUAGE PolyKinds #-}------------------------------------------------------------------------------- |-- Module : Data.Proxy-- License : BSD-style (see the LICENSE file in the distribution)---- Maintainer : libraries@haskell.org-- Stability : stable-- Portability : portable---- Definition of a Proxy type (poly-kinded in GHC)---- @since 4.7.0.0-----------------------------------------------------------------------------moduleData.Proxy(Proxy (..),asProxyTypeOf ,KProxy (..))whereimportGHC.Base importGHC.Show importGHC.Read importGHC.Enum importGHC.Arr -- $setup-- >>> import Data.Void-- >>> import Prelude-- | '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-- ProxydataProxy t =Proxy deriving(Proxy t
Proxy t -> Proxy t -> Bounded (Proxy t)
forall a. a -> a -> Bounded a
forall k (t :: k). Proxy t
$cminBound :: forall k (t :: k). Proxy t
minBound :: Proxy t
$cmaxBound :: forall k (t :: k). Proxy t
maxBound :: Proxy t
Bounded -- ^ @since 4.7.0.0,ReadPrec [Proxy t]
ReadPrec (Proxy t)
Int -> ReadS (Proxy t)
ReadS [Proxy t]
(Int -> ReadS (Proxy t))
-> ReadS [Proxy t]
-> ReadPrec (Proxy t)
-> ReadPrec [Proxy t]
-> Read (Proxy t)
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall k (t :: k). ReadPrec [Proxy t]
forall k (t :: k). ReadPrec (Proxy t)
forall k (t :: k). Int -> ReadS (Proxy t)
forall k (t :: k). ReadS [Proxy t]
$creadsPrec :: forall k (t :: k). Int -> ReadS (Proxy t)
readsPrec :: Int -> ReadS (Proxy t)
$creadList :: forall k (t :: k). ReadS [Proxy t]
readList :: ReadS [Proxy t]
$creadPrec :: forall k (t :: k). ReadPrec (Proxy t)
readPrec :: ReadPrec (Proxy t)
$creadListPrec :: forall k (t :: k). ReadPrec [Proxy t]
readListPrec :: ReadPrec [Proxy t]
Read -- ^ @since 4.7.0.0)-- | 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 onlydataKProxy (t ::Type )=KProxy -- It's common to use (undefined :: Proxy t) and (Proxy :: Proxy t)-- interchangeably, so all of these instances are hand-written to be-- lazy in Proxy arguments.-- | @since 4.7.0.0instanceEq (Proxy s )whereProxy s
_== :: Proxy s -> Proxy s -> Bool
== Proxy s
_=Bool
True -- | @since 4.7.0.0instanceOrd (Proxy s )wherecompare :: Proxy s -> Proxy s -> Ordering
compare Proxy s
_Proxy s
_=Ordering
EQ -- | @since 4.7.0.0instanceShow (Proxy s )whereshowsPrec :: Int -> Proxy s -> ShowS
showsPrec Int
_Proxy s
_=String -> ShowS
showString String
"Proxy"-- | @since 4.7.0.0instanceEnum (Proxy s )wheresucc :: Proxy s -> Proxy s
succ Proxy s
_=String -> Proxy s
forall a. String -> a
errorWithoutStackTrace String
"Proxy.succ"pred :: Proxy s -> Proxy s
pred Proxy s
_=String -> Proxy s
forall a. String -> a
errorWithoutStackTrace String
"Proxy.pred"fromEnum :: Proxy s -> Int
fromEnum Proxy s
_=Int
0toEnum :: Int -> Proxy s
toEnum Int
0=Proxy s
forall k (t :: k). Proxy t
Proxy toEnum Int
_=String -> Proxy s
forall a. String -> a
errorWithoutStackTrace String
"Proxy.toEnum: 0 expected"enumFrom :: Proxy s -> [Proxy s]
enumFrom Proxy s
_=[Proxy s
forall k (t :: k). Proxy t
Proxy ]enumFromThen :: Proxy s -> Proxy s -> [Proxy s]
enumFromThen Proxy s
_Proxy s
_=[Proxy s
forall k (t :: k). Proxy t
Proxy ]enumFromThenTo :: Proxy s -> Proxy s -> Proxy s -> [Proxy s]
enumFromThenTo Proxy s
_Proxy s
_Proxy s
_=[Proxy s
forall k (t :: k). Proxy t
Proxy ]enumFromTo :: Proxy s -> Proxy s -> [Proxy s]
enumFromTo Proxy s
_Proxy s
_=[Proxy s
forall k (t :: k). Proxy t
Proxy ]-- | @since 4.7.0.0instanceIx (Proxy s )whererange :: (Proxy s, Proxy s) -> [Proxy s]
range (Proxy s, Proxy s)
_=[Proxy s
forall k (t :: k). Proxy t
Proxy ]index :: (Proxy s, Proxy s) -> Proxy s -> Int
index (Proxy s, Proxy s)
_Proxy s
_=Int
0inRange :: (Proxy s, Proxy s) -> Proxy s -> Bool
inRange (Proxy s, Proxy s)
_Proxy s
_=Bool
True rangeSize :: (Proxy s, Proxy s) -> Int
rangeSize (Proxy s, Proxy s)
_=Int
1unsafeIndex :: (Proxy s, Proxy s) -> Proxy s -> Int
unsafeIndex (Proxy s, Proxy s)
_Proxy s
_=Int
0unsafeRangeSize :: (Proxy s, Proxy s) -> Int
unsafeRangeSize (Proxy s, Proxy s)
_=Int
1-- | @since 4.9.0.0instanceSemigroup (Proxy s )whereProxy s
_<> :: Proxy s -> Proxy s -> Proxy s
<> Proxy s
_=Proxy s
forall k (t :: k). Proxy t
Proxy sconcat :: NonEmpty (Proxy s) -> Proxy s
sconcat NonEmpty (Proxy s)
_=Proxy s
forall k (t :: k). Proxy t
Proxy stimes :: forall b. Integral b => b -> Proxy s -> Proxy s
stimes b
_Proxy s
_=Proxy s
forall k (t :: k). Proxy t
Proxy -- | @since 4.7.0.0instanceMonoid (Proxy s )wheremempty :: Proxy s
mempty =Proxy s
forall k (t :: k). Proxy t
Proxy mconcat :: [Proxy s] -> Proxy s
mconcat [Proxy s]
_=Proxy s
forall k (t :: k). Proxy t
Proxy -- | @since 4.7.0.0instanceFunctor Proxy wherefmap :: forall a b. (a -> b) -> Proxy a -> Proxy b
fmap a -> b
_Proxy a
_=Proxy b
forall k (t :: k). Proxy t
Proxy {-# INLINEfmap #-}-- | @since 4.7.0.0instanceApplicative Proxy wherepure :: forall a. a -> Proxy a
pure a
_=Proxy a
forall k (t :: k). Proxy t
Proxy {-# INLINEpure #-}Proxy (a -> b)
_<*> :: forall a b. Proxy (a -> b) -> Proxy a -> Proxy b
<*> Proxy a
_=Proxy b
forall k (t :: k). Proxy t
Proxy {-# INLINE(<*>)#-}-- | @since 4.9.0.0instanceAlternative Proxy whereempty :: forall a. Proxy a
empty =Proxy a
forall k (t :: k). Proxy t
Proxy {-# INLINEempty #-}Proxy a
_<|> :: forall a. Proxy a -> Proxy a -> Proxy a
<|> Proxy a
_=Proxy a
forall k (t :: k). Proxy t
Proxy {-# INLINE(<|>)#-}-- | @since 4.7.0.0instanceMonad Proxy whereProxy a
_>>= :: forall a b. Proxy a -> (a -> Proxy b) -> Proxy b
>>= a -> Proxy b
_=Proxy b
forall k (t :: k). Proxy t
Proxy {-# INLINE(>>=)#-}-- | @since 4.9.0.0instanceMonadPlus Proxy -- | '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)) :: Word8asProxyTypeOf ::a ->proxy a ->a asProxyTypeOf :: forall a (proxy :: * -> *). a -> proxy a -> a
asProxyTypeOf =a -> proxy a -> a
forall a b. a -> b -> a
const {-# INLINEasProxyTypeOf #-}

AltStyle によって変換されたページ (->オリジナル) /