base-4.9.1.0: Basic libraries

CopyrightConor McBride and Ross Paterson 2005
LicenseBSD-style (see the LICENSE file in the distribution)
Maintainerlibraries@haskell.org
Stabilityexperimental
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Functor.Const

Description

 

Synopsis

Documentation

newtype Const a b Source #

The Const functor.

Constructors

Const 

Fields

Instances

Bifunctor (Const *) Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> Const * a c -> Const * b d Source #

first :: (a -> b) -> Const * a c -> Const * b c Source #

second :: (b -> c) -> Const * a b -> Const * a c Source #

Show2 (Const *) Source # 

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Const * a b -> ShowS Source #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Const * a b] -> ShowS Source #

Read2 (Const *) Source # 

Methods

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 #

Ord2 (Const *) Source # 

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Const * a c -> Const * b d -> Ordering Source #

Eq2 (Const *) Source # 

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Const * a c -> Const * b d -> Bool Source #

Functor (Const * m) Source # 

Methods

fmap :: (a -> b) -> Const * m a -> Const * m b Source #

(<$) :: a -> Const * m b -> Const * m a Source #

Monoid m => Applicative (Const * m) Source # 

Methods

pure :: a -> Const * m a Source #

(<*>) :: Const * m (a -> b) -> Const * m a -> Const * m b Source #

(*>) :: Const * m a -> Const * m b -> Const * m b Source #

(<*) :: Const * m a -> Const * m b -> Const * m a Source #

Foldable (Const * m) Source # 

Methods

fold :: Monoid m => Const * m m -> m Source #

foldMap :: Monoid m => (a -> m) -> Const * m a -> m 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 #

sum :: Num a => Const * m a -> a Source #

product :: Num a => Const * m a -> a Source #

Traversable (Const * m) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Const * m a -> f (Const * m b) Source #

sequenceA :: Applicative f => Const * m (f a) -> f (Const * m a) Source #

mapM :: Monad m => (a -> m b) -> Const * m a -> m (Const * m b) Source #

sequence :: Monad m => Const * m (m a) -> m (Const * m a) Source #

Generic1 (Const * a) Source # 

Associated Types

type Rep1 (Const * a :: * -> *) :: * -> * Source #

Methods

from1 :: Const * a a -> Rep1 (Const * a) a Source #

to1 :: Rep1 (Const * a) a -> Const * a a Source #

Show a => Show1 (Const * a) Source # 

Methods

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

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

Read a => Read1 (Const * a) Source # 

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Const * a a) Source #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Const * a a] Source #

Ord a => Ord1 (Const * a) Source # 

Methods

liftCompare :: (a -> b -> Ordering) -> Const * a a -> Const * a b -> Ordering Source #

Eq a => Eq1 (Const * a) Source # 

Methods

liftEq :: (a -> b -> Bool) -> Const * a a -> Const * a b -> Bool Source #

Bounded a => Bounded (Const k a b) Source # 

Methods

minBound :: Const k a b Source #

maxBound :: Const k a b Source #

Enum a => Enum (Const k a b) Source # 

Methods

succ :: Const k a b -> Const k a b Source #

pred :: Const k a b -> Const k a b Source #

toEnum :: Int -> Const k a b Source #

fromEnum :: Const k a b -> Int Source #

enumFrom :: Const k a b -> [Const k a b] Source #

enumFromThen :: Const k a b -> Const k a b -> [Const k a b] Source #

enumFromTo :: Const k a b -> Const k a b -> [Const k a b] Source #

enumFromThenTo :: Const k a b -> Const k a b -> Const k a b -> [Const k a b] Source #

Eq a => Eq (Const k a b) Source # 

Methods

(==) :: Const k a b -> Const k a b -> Bool #

(/=) :: Const k a b -> Const k a b -> Bool #

Floating a => Floating (Const k a b) Source # 

Methods

pi :: Const k a b Source #

exp :: Const k a b -> Const k a b Source #

log :: Const k a b -> Const k a b Source #

sqrt :: Const k a b -> Const k a b Source #

(**) :: Const k a b -> Const k a b -> Const k a b Source #

logBase :: Const k a b -> Const k a b -> Const k a b Source #

sin :: Const k a b -> Const k a b Source #

cos :: Const k a b -> Const k a b Source #

tan :: Const k a b -> Const k a b Source #

asin :: Const k a b -> Const k a b Source #

acos :: Const k a b -> Const k a b Source #

atan :: Const k a b -> Const k a b Source #

sinh :: Const k a b -> Const k a b Source #

cosh :: Const k a b -> Const k a b Source #

tanh :: Const k a b -> Const k a b Source #

asinh :: Const k a b -> Const k a b Source #

acosh :: Const k a b -> Const k a b Source #

atanh :: Const k a b -> Const k a b Source #

log1p :: Const k a b -> Const k a b Source #

expm1 :: Const k a b -> Const k a b Source #

log1pexp :: Const k a b -> Const k a b Source #

log1mexp :: Const k a b -> Const k a b Source #

Fractional a => Fractional (Const k a b) Source # 

Methods

(/) :: Const k a b -> Const k a b -> Const k a b Source #

recip :: Const k a b -> Const k a b Source #

fromRational :: Rational -> Const k a b Source #

Integral a => Integral (Const k a b) Source # 

Methods

quot :: Const k a b -> Const k a b -> Const k a b Source #

rem :: Const k a b -> Const k a b -> Const k a b Source #

div :: Const k a b -> Const k a b -> Const k a b Source #

mod :: Const k a b -> Const k a b -> Const k a b Source #

quotRem :: Const k a b -> Const k a b -> (Const k a b, Const k a b) Source #

divMod :: Const k a b -> Const k a b -> (Const k a b, Const k a b) Source #

toInteger :: Const k a b -> Integer Source #

Num a => Num (Const k a b) Source # 

Methods

(+) :: Const k a b -> Const k a b -> Const k a b Source #

(-) :: Const k a b -> Const k a b -> Const k a b Source #

(*) :: Const k a b -> Const k a b -> Const k a b Source #

negate :: Const k a b -> Const k a b Source #

abs :: Const k a b -> Const k a b Source #

signum :: Const k a b -> Const k a b Source #

fromInteger :: Integer -> Const k a b Source #

Ord a => Ord (Const k a b) Source # 

Methods

compare :: Const k a b -> Const k a b -> Ordering #

(<) :: Const k a b -> Const k a b -> Bool #

(<=) :: Const k a b -> Const k a b -> Bool #

(>) :: Const k a b -> Const k a b -> Bool #

(>=) :: Const k a b -> Const k a b -> Bool #

max :: Const k a b -> Const k a b -> Const k a b #

min :: Const k a b -> Const k a b -> Const k a b #

Read a => Read (Const k a b) Source #

This instance would be equivalent to the derived instances of the Const newtype if the runConst field were removed

Real a => Real (Const k a b) Source # 

Methods

toRational :: Const k a b -> Rational Source #

RealFloat a => RealFloat (Const k a b) Source # 

Methods

floatRadix :: Const k a b -> Integer Source #

floatDigits :: Const k a b -> Int Source #

floatRange :: Const k a b -> (Int, Int) Source #

decodeFloat :: Const k a b -> (Integer, Int) Source #

encodeFloat :: Integer -> Int -> Const k a b Source #

exponent :: Const k a b -> Int Source #

significand :: Const k a b -> Const k a b Source #

scaleFloat :: Int -> Const k a b -> Const k a b Source #

isNaN :: Const k a b -> Bool Source #

isInfinite :: Const k a b -> Bool Source #

isDenormalized :: Const k a b -> Bool Source #

isNegativeZero :: Const k a b -> Bool Source #

isIEEE :: Const k a b -> Bool Source #

atan2 :: Const k a b -> Const k a b -> Const k a b Source #

RealFrac a => RealFrac (Const k a b) Source # 

Methods

properFraction :: Integral b => Const k a b -> (b, Const k a b) Source #

truncate :: Integral b => Const k a b -> b Source #

round :: Integral b => Const k a b -> b Source #

ceiling :: Integral b => Const k a b -> b Source #

floor :: Integral b => Const k a b -> b Source #

Show a => Show (Const k a b) Source #

This instance would be equivalent to the derived instances of the Const newtype if the runConst field were removed

Methods

showsPrec :: Int -> Const k a b -> ShowS Source #

show :: Const k a b -> String Source #

showList :: [Const k a b] -> ShowS Source #

Ix a => Ix (Const k a b) Source # 

Methods

range :: (Const k a b, Const k a b) -> [Const k a b] Source #

index :: (Const k a b, Const k a b) -> Const k a b -> Int Source #

unsafeIndex :: (Const k a b, Const k a b) -> Const k a b -> Int

inRange :: (Const k a b, Const k a b) -> Const k a b -> Bool Source #

rangeSize :: (Const k a b, Const k a b) -> Int Source #

unsafeRangeSize :: (Const k a b, Const k a b) -> Int

IsString a => IsString (Const * a b) Source # 

Methods

fromString :: String -> Const * a b Source #

Generic (Const k a b) Source # 

Associated Types

type Rep (Const k a b) :: * -> * Source #

Methods

from :: Const k a b -> Rep (Const k a b) x Source #

to :: Rep (Const k a b) x -> Const k a b Source #

Semigroup a => Semigroup (Const k a b) Source # 

Methods

(<>) :: Const k a b -> Const k a b -> Const k a b Source #

sconcat :: NonEmpty (Const k a b) -> Const k a b Source #

stimes :: Integral b => b -> Const k a b -> Const k a b Source #

Monoid a => Monoid (Const k a b) Source # 

Methods

mempty :: Const k a b Source #

mappend :: Const k a b -> Const k a b -> Const k a b Source #

mconcat :: [Const k a b] -> Const k a b Source #

FiniteBits a => FiniteBits (Const k a b) Source # 
Bits a => Bits (Const k a b) Source # 

Methods

(.&.) :: Const k a b -> Const k a b -> Const k a b Source #

(.|.) :: Const k a b -> Const k a b -> Const k a b Source #

xor :: Const k a b -> Const k a b -> Const k a b Source #

complement :: Const k a b -> Const k a b Source #

shift :: Const k a b -> Int -> Const k a b Source #

rotate :: Const k a b -> Int -> Const k a b Source #

zeroBits :: Const k a b Source #

bit :: Int -> Const k a b Source #

setBit :: Const k a b -> Int -> Const k a b Source #

clearBit :: Const k a b -> Int -> Const k a b Source #

complementBit :: Const k a b -> Int -> Const k a b Source #

testBit :: Const k a b -> Int -> Bool Source #

bitSizeMaybe :: Const k a b -> Maybe Int Source #

bitSize :: Const k a b -> Int Source #

isSigned :: Const k a b -> Bool Source #

shiftL :: Const k a b -> Int -> Const k a b Source #

unsafeShiftL :: Const k a b -> Int -> Const k a b Source #

shiftR :: Const k a b -> Int -> Const k a b Source #

unsafeShiftR :: Const k a b -> Int -> Const k a b Source #

rotateL :: Const k a b -> Int -> Const k a b Source #

rotateR :: Const k a b -> Int -> Const k a b Source #

popCount :: Const k a b -> Int Source #

Storable a => Storable (Const k a b) Source # 

Methods

sizeOf :: Const k a b -> Int Source #

alignment :: Const k a b -> Int Source #

peekElemOff :: Ptr (Const k a b) -> Int -> IO (Const k a b) Source #

pokeElemOff :: Ptr (Const k a b) -> Int -> Const k a b -> IO () Source #

peekByteOff :: Ptr b -> Int -> IO (Const k a b) Source #

pokeByteOff :: Ptr b -> Int -> Const k a b -> IO () Source #

peek :: Ptr (Const k a b) -> IO (Const k a b) Source #

poke :: Ptr (Const k a b) -> Const k a b -> IO () Source #

type Rep1 (Const * a) Source # 
type Rep1 (Const * a) = D1 (MetaData "Const" "Data.Functor.Const" "base" True) (C1 (MetaCons "Const" PrefixI True) (S1 (MetaSel (Just Symbol "getConst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep (Const k a b) Source # 
type Rep (Const k a b) = D1 (MetaData "Const" "Data.Functor.Const" "base" True) (C1 (MetaCons "Const" PrefixI True) (S1 (MetaSel (Just Symbol "getConst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))