{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE PolyKinds #-}
module Data.Proxy
(
Proxy(..), asProxyTypeOf
, KProxy(..)
) where
import GHC.Base
import GHC.Show
import GHC.Read
import GHC.Enum
import GHC.Arr
data Proxy 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
, 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
)
data KProxy (t :: Type) = KProxy
instance Eq (Proxy s) where
Proxy s
_ == :: Proxy s -> Proxy s -> Bool
== Proxy s
_ = Bool
True
instance Ord (Proxy s) where
compare :: Proxy s -> Proxy s -> Ordering
compare Proxy s
_ Proxy s
_ = Ordering
EQ
instance Show (Proxy s) where
showsPrec :: Int -> Proxy s -> ShowS
showsPrec Int
_ Proxy s
_ = String -> ShowS
showString String
"Proxy"
instance Enum (Proxy s) where
succ :: 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
0
toEnum :: 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]
instance Ix (Proxy s) where
range :: (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
0
inRange :: (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
1
unsafeIndex :: (Proxy s, Proxy s) -> Proxy s -> Int
unsafeIndex (Proxy s, Proxy s)
_ Proxy s
_ = Int
0
unsafeRangeSize :: (Proxy s, Proxy s) -> Int
unsafeRangeSize (Proxy s, Proxy s)
_ = Int
1
instance Semigroup (Proxy s) where
Proxy 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
instance Monoid (Proxy s) where
mempty :: 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
instance Functor Proxy where
fmap :: forall a b. (a -> b) -> Proxy a -> Proxy b
fmap a -> b
_ Proxy a
_ = Proxy b
forall k (t :: k). Proxy t
Proxy
{-# INLINE fmap #-}
instance Applicative Proxy where
pure :: forall a. a -> Proxy a
pure a
_ = Proxy a
forall k (t :: k). Proxy t
Proxy
{-# INLINE pure #-}
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 (<*>) #-}
instance Alternative Proxy where
empty :: forall a. Proxy a
empty = Proxy a
forall k (t :: k). Proxy t
Proxy
{-# INLINE empty #-}
Proxy a
_ <|> :: forall a. Proxy a -> Proxy a -> Proxy a
<|> Proxy a
_ = Proxy a
forall k (t :: k). Proxy t
Proxy
{-# INLINE (<|>) #-}
instance Monad Proxy where
Proxy a
_ >>= :: forall a b. Proxy a -> (a -> Proxy b) -> Proxy b
>>= a -> Proxy b
_ = Proxy b
forall k (t :: k). Proxy t
Proxy
{-# INLINE (>>=) #-}
instance MonadPlus Proxy
asProxyTypeOf :: a -> proxy a -> a
asProxyTypeOf :: forall a (proxy :: * -> *). a -> proxy a -> a
asProxyTypeOf = a -> proxy a -> a
forall a b. a -> b -> a
const
{-# INLINE asProxyTypeOf #-}