base-4.15.0.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

Instances details
Generic1 (Const a :: k -> Type) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Associated Types

type Rep1 (Const a) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k0). Const a a0 -> Rep1 (Const a) a0 Source #

to1 :: forall (a0 :: k0). Rep1 (Const a) a0 -> Const a a0 Source #

Show2 (Const :: Type -> Type -> Type) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

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 :: Type -> Type -> Type) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

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 #

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) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Eq2 (Const :: Type -> Type -> Type) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Bifunctor (Const :: Type -> Type -> Type) #

Since: base-4.8.0.0

Instance details

Defined in Data.Bifunctor

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 #

Bifoldable (Const :: Type -> Type -> Type) #

Since: base-4.10.0.0

Instance details

Defined in Data.Bifoldable

Methods

bifold :: Monoid m => Const m m -> m Source #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Const a b -> m Source #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Const a b -> c Source #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Const a b -> c Source #

Bitraversable (Const :: Type -> Type -> Type) #

Since: base-4.10.0.0

Instance details

Defined in Data.Bitraversable

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Const a b -> f (Const c d) Source #

Functor (Const m :: Type -> Type) #

Since: base-2.1

Instance details

Defined in Data.Functor.Const

Methods

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

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

Monoid m => Applicative (Const m :: Type -> Type) #

Since: base-2.0.1

Instance details

Defined in Data.Functor.Const

Methods

pure :: a -> Const m a Source #

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

liftA2 :: (a -> b -> c) -> Const m a -> Const m b -> Const m c Source #

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

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

Foldable (Const m :: Type -> Type) #

Since: base-4.7.0.0

Instance details

Defined in Data.Functor.Const

Methods

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 #

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

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

Traversable (Const m :: Type -> Type) #

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

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 m0 => (a -> m0 b) -> Const m a -> m0 (Const m b) Source #

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

Show a => Show1 (Const a :: Type -> Type) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

Read a => Read1 (Const a :: Type -> Type) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Eq a => Eq1 (Const a :: Type -> Type) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Contravariant (Const a :: Type -> Type) # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a0) -> Const a a0 -> Const a a' Source #

(>$) :: b -> Const a b -> Const a a0 Source #

Bounded a => Bounded (Const a b) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

minBound :: Const a b Source #

maxBound :: Const a b Source #

Enum a => Enum (Const a b) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

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) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

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

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

Floating a => Floating (Const a b) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

pi :: Const a b Source #

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 #

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

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

Fractional a => Fractional (Const a b) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

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

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

fromRational :: Rational -> Const a b Source #

Integral a => Integral (Const a b) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

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 #

toInteger :: Const a b -> Integer Source #

(Typeable k, Data a, Typeable b) => Data (Const a b) #

Since: base-4.10.0.0

Instance details

Defined in Data.Data

Methods

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) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

(+) :: 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) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

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

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

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

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

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

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

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

Read a => Read (Const a b) #

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

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Const

Real a => Real (Const a b) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

toRational :: Const a b -> Rational Source #

RealFloat a => RealFloat (Const a b) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

RealFrac a => RealFrac (Const a b) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

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

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

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

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

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

Show a => Show (Const a b) #

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

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Const

Methods

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

show :: Const a b -> String Source #

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

Ix a => Ix (Const a b) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

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

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

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

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

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

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

IsString a => IsString (Const a b) #

Since: base-4.9.0.0

Instance details

Defined in Data.String

Methods

fromString :: String -> Const a b Source #

Generic (Const a b) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Associated Types

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

Methods

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

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

Semigroup a => Semigroup (Const a b) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

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

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

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

Monoid a => Monoid (Const a b) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

mempty :: Const a b Source #

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

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

FiniteBits a => FiniteBits (Const a b) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Bits a => Bits (Const a b) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

(.&.) :: 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 #

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

popCount :: Const a b -> Int Source #

Storable a => Storable (Const a b) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

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 #

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

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

type Rep1 (Const a :: k -> Type) # 
Instance details

Defined in Data.Functor.Const

type Rep1 (Const a :: k -> Type) = D1 ('MetaData "Const" "Data.Functor.Const" "base" 'True) (C1 ('MetaCons "Const" 'PrefixI 'True) (S1 ('MetaSel ('Just "getConst") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
type Rep (Const a b) # 
Instance details

Defined in Data.Functor.Const

type Rep (Const a b) = D1 ('MetaData "Const" "Data.Functor.Const" "base" 'True) (C1 ('MetaCons "Const" 'PrefixI 'True) (S1 ('MetaSel ('Just "getConst") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))