Copyright | Conor McBride and Ross Paterson 2005 |
---|---|
License | BSD-style (see the LICENSE file in the distribution) |
Maintainer | libraries@haskell.org |
Stability | experimental |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Documentation
The Const
functor.
Instances
Generic1 (Const a :: k -> Type) Source # | Since: 4.9.0.0 |
Show2 (Const :: Type -> Type -> Type) Source # | Since: 4.9.0.0 |
Read2 (Const :: Type -> Type -> Type) Source # | Since: 4.9.0.0 |
Defined in Data.Functor.Classes liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Const a b) Source # liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Const a b] Source # liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Const a b) Source # liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Const a b] Source # | |
Ord2 (Const :: Type -> Type -> Type) Source # | Since: 4.9.0.0 |
Defined in Data.Functor.Classes | |
Eq2 (Const :: Type -> Type -> Type) Source # | Since: 4.9.0.0 |
Bifunctor (Const :: Type -> Type -> Type) Source # | Since: 4.8.0.0 |
Bifoldable (Const :: Type -> Type -> Type) Source # | Since: 4.10.0.0 |
Bitraversable (Const :: Type -> Type -> Type) Source # | Since: 4.10.0.0 |
Defined in Data.Bitraversable bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Const a b -> f (Const c d) Source # | |
Functor (Const m :: Type -> Type) Source # | Since: 2.1 |
Monoid m => Applicative (Const m :: Type -> Type) Source # | Since: 2.0.1 |
Foldable (Const m :: Type -> Type) Source # | Since: 4.7.0.0 |
Defined in Data.Functor.Const fold :: Monoid m0 => Const m m0 -> m0 Source # foldMap :: Monoid m0 => (a -> m0) -> Const m a -> m0 Source # foldMap' :: Monoid m0 => (a -> m0) -> Const m a -> m0 Source # foldr :: (a -> b -> b) -> b -> Const m a -> b Source # foldr' :: (a -> b -> b) -> b -> Const m a -> b Source # foldl :: (b -> a -> b) -> b -> Const m a -> b Source # foldl' :: (b -> a -> b) -> b -> Const m a -> b Source # foldr1 :: (a -> a -> a) -> Const m a -> a Source # foldl1 :: (a -> a -> a) -> Const m a -> a Source # toList :: Const m a -> [a] Source # null :: Const m a -> Bool Source # length :: Const m a -> Int Source # elem :: Eq a => a -> Const m a -> Bool Source # maximum :: Ord a => Const m a -> a Source # minimum :: Ord a => Const m a -> a Source # | |
Traversable (Const m :: Type -> Type) Source # | Since: 4.7.0.0 |
Defined in Data.Traversable | |
Show a => Show1 (Const a :: Type -> Type) Source # | Since: 4.9.0.0 |
Read a => Read1 (Const a :: Type -> Type) Source # | Since: 4.9.0.0 |
Defined in Data.Functor.Classes liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Const a a0) Source # liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Const a a0] Source # liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Const a a0) Source # liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Const a a0] Source # | |
Ord a => Ord1 (Const a :: Type -> Type) Source # | Since: 4.9.0.0 |
Defined in Data.Functor.Classes | |
Eq a => Eq1 (Const a :: Type -> Type) Source # | Since: 4.9.0.0 |
Contravariant (Const a :: Type -> Type) Source # | |
Bounded a => Bounded (Const a b) Source # | Since: 4.9.0.0 |
Enum a => Enum (Const a b) Source # | Since: 4.9.0.0 |
Defined in Data.Functor.Const succ :: Const a b -> Const a b Source # pred :: Const a b -> Const a b Source # toEnum :: Int -> Const a b Source # fromEnum :: Const a b -> Int Source # enumFrom :: Const a b -> [Const a b] Source # enumFromThen :: Const a b -> Const a b -> [Const a b] Source # enumFromTo :: Const a b -> Const a b -> [Const a b] Source # enumFromThenTo :: Const a b -> Const a b -> Const a b -> [Const a b] Source # | |
Eq a => Eq (Const a b) Source # | Since: 4.9.0.0 |
Floating a => Floating (Const a b) Source # | Since: 4.9.0.0 |
Defined in Data.Functor.Const exp :: Const a b -> Const a b Source # log :: Const a b -> Const a b Source # sqrt :: Const a b -> Const a b Source # (**) :: Const a b -> Const a b -> Const a b Source # logBase :: Const a b -> Const a b -> Const a b Source # sin :: Const a b -> Const a b Source # cos :: Const a b -> Const a b Source # tan :: Const a b -> Const a b Source # asin :: Const a b -> Const a b Source # acos :: Const a b -> Const a b Source # atan :: Const a b -> Const a b Source # sinh :: Const a b -> Const a b Source # cosh :: Const a b -> Const a b Source # tanh :: Const a b -> Const a b Source # asinh :: Const a b -> Const a b Source # acosh :: Const a b -> Const a b Source # atanh :: Const a b -> Const a b Source # log1p :: Const a b -> Const a b Source # expm1 :: Const a b -> Const a b Source # | |
Fractional a => Fractional (Const a b) Source # | Since: 4.9.0.0 |
Integral a => Integral (Const a b) Source # | Since: 4.9.0.0 |
Defined in Data.Functor.Const quot :: Const a b -> Const a b -> Const a b Source # rem :: Const a b -> Const a b -> Const a b Source # div :: Const a b -> Const a b -> Const a b Source # mod :: Const a b -> Const a b -> Const a b Source # quotRem :: Const a b -> Const a b -> (Const a b, Const a b) Source # divMod :: Const a b -> Const a b -> (Const a b, Const a b) Source # | |
(Typeable k, Data a, Typeable b) => Data (Const a b) Source # | Since: 4.10.0.0 |
Defined in Data.Data gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Const a b -> c (Const a b) Source # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Const a b) Source # toConstr :: Const a b -> Constr Source # dataTypeOf :: Const a b -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Const a b)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Const a b)) Source # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Const a b -> Const a b Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Const a b -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Const a b -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Const a b -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Const a b -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Const a b -> m (Const a b) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Const a b -> m (Const a b) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Const a b -> m (Const a b) Source # | |
Num a => Num (Const a b) Source # | Since: 4.9.0.0 |
Defined in Data.Functor.Const (+) :: Const a b -> Const a b -> Const a b Source # (-) :: Const a b -> Const a b -> Const a b Source # (*) :: Const a b -> Const a b -> Const a b Source # negate :: Const a b -> Const a b Source # abs :: Const a b -> Const a b Source # signum :: Const a b -> Const a b Source # fromInteger :: Integer -> Const a b Source # | |
Ord a => Ord (Const a b) Source # | Since: 4.9.0.0 |
Defined in Data.Functor.Const | |
Read a => Read (Const a b) Source # | This instance would be equivalent to the derived instances of the
Since: 4.8.0.0 |
Real a => Real (Const a b) Source # | Since: 4.9.0.0 |
Defined in Data.Functor.Const toRational :: Const a b -> Rational Source # | |
RealFloat a => RealFloat (Const a b) Source # | Since: 4.9.0.0 |
Defined in Data.Functor.Const floatRadix :: Const a b -> Integer Source # floatDigits :: Const a b -> Int Source # floatRange :: Const a b -> (Int, Int) Source # decodeFloat :: Const a b -> (Integer, Int) Source # encodeFloat :: Integer -> Int -> Const a b Source # exponent :: Const a b -> Int Source # significand :: Const a b -> Const a b Source # scaleFloat :: Int -> Const a b -> Const a b Source # isNaN :: Const a b -> Bool Source # isInfinite :: Const a b -> Bool Source # isDenormalized :: Const a b -> Bool Source # isNegativeZero :: Const a b -> Bool Source # | |
RealFrac a => RealFrac (Const a b) Source # | Since: 4.9.0.0 |
Show a => Show (Const a b) Source # | This instance would be equivalent to the derived instances of the
Since: 4.8.0.0 |
Ix a => Ix (Const a b) Source # | Since: 4.9.0.0 |
Defined in Data.Functor.Const | |
IsString a => IsString (Const a b) Source # | Since: 4.9.0.0 |
Defined in Data.String fromString :: String -> Const a b Source # | |
Generic (Const a b) Source # | Since: 4.9.0.0 |
Semigroup a => Semigroup (Const a b) Source # | Since: 4.9.0.0 |
Monoid a => Monoid (Const a b) Source # | Since: 4.9.0.0 |
FiniteBits a => FiniteBits (Const a b) Source # | Since: 4.9.0.0 |
Defined in Data.Functor.Const finiteBitSize :: Const a b -> Int Source # countLeadingZeros :: Const a b -> Int Source # countTrailingZeros :: Const a b -> Int Source # | |
Bits a => Bits (Const a b) Source # | Since: 4.9.0.0 |
Defined in Data.Functor.Const (.&.) :: Const a b -> Const a b -> Const a b Source # (.|.) :: Const a b -> Const a b -> Const a b Source # xor :: Const a b -> Const a b -> Const a b Source # complement :: Const a b -> Const a b Source # shift :: Const a b -> Int -> Const a b Source # rotate :: Const a b -> Int -> Const a b Source # zeroBits :: Const a b Source # bit :: Int -> Const a b Source # setBit :: Const a b -> Int -> Const a b Source # clearBit :: Const a b -> Int -> Const a b Source # complementBit :: Const a b -> Int -> Const a b Source # testBit :: Const a b -> Int -> Bool Source # bitSizeMaybe :: Const a b -> Maybe Int Source # bitSize :: Const a b -> Int Source # isSigned :: Const a b -> Bool Source # shiftL :: Const a b -> Int -> Const a b Source # unsafeShiftL :: Const a b -> Int -> Const a b Source # shiftR :: Const a b -> Int -> Const a b Source # unsafeShiftR :: Const a b -> Int -> Const a b Source # rotateL :: Const a b -> Int -> Const a b Source # | |
Storable a => Storable (Const a b) Source # | Since: 4.9.0.0 |
Defined in Data.Functor.Const sizeOf :: Const a b -> Int Source # alignment :: Const a b -> Int Source # peekElemOff :: Ptr (Const a b) -> Int -> IO (Const a b) Source # pokeElemOff :: Ptr (Const a b) -> Int -> Const a b -> IO () Source # peekByteOff :: Ptr b0 -> Int -> IO (Const a b) Source # pokeByteOff :: Ptr b0 -> Int -> Const a b -> IO () Source # | |
type Rep1 (Const a :: k -> Type) Source # | |
Defined in Data.Functor.Const | |
type Rep (Const a b) Source # | |
Defined in Data.Functor.Const |