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

Bifunctor (Const (TYPE Lifted)) 

Methods

bimap :: (a -> b) -> (c -> d) -> Const (TYPE Lifted) a c -> Const (TYPE Lifted) b d Source

first :: (a -> b) -> Const (TYPE Lifted) a c -> Const (TYPE Lifted) b c Source

second :: (b -> c) -> Const (TYPE Lifted) a b -> Const (TYPE Lifted) a c Source

Show2 (Const (TYPE Lifted)) 

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Const (TYPE Lifted) a b -> ShowS Source

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Const (TYPE Lifted) a b] -> ShowS Source

Read2 (Const (TYPE Lifted)) 

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Const (TYPE Lifted) a b) Source

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Const (TYPE Lifted) a b] Source

Ord2 (Const (TYPE Lifted)) 

Methods

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

Eq2 (Const (TYPE Lifted)) 

Methods

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

Functor (Const (TYPE Lifted) m) 

Methods

fmap :: (a -> b) -> Const (TYPE Lifted) m a -> Const (TYPE Lifted) m b Source

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

Monoid m => Applicative (Const (TYPE Lifted) m) 

Methods

pure :: a -> Const (TYPE Lifted) m a Source

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

(*>) :: Const (TYPE Lifted) m a -> Const (TYPE Lifted) m b -> Const (TYPE Lifted) m b Source

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

Foldable (Const (TYPE Lifted) m) 

Methods

fold :: Monoid m => Const (TYPE Lifted) m m -> m Source

foldMap :: Monoid m => (a -> m) -> Const (TYPE Lifted) m a -> m Source

foldr :: (a -> b -> b) -> b -> Const (TYPE Lifted) m a -> b Source

foldr' :: (a -> b -> b) -> b -> Const (TYPE Lifted) m a -> b Source

foldl :: (b -> a -> b) -> b -> Const (TYPE Lifted) m a -> b Source

foldl' :: (b -> a -> b) -> b -> Const (TYPE Lifted) m a -> b Source

foldr1 :: (a -> a -> a) -> Const (TYPE Lifted) m a -> a Source

foldl1 :: (a -> a -> a) -> Const (TYPE Lifted) m a -> a Source

toList :: Const (TYPE Lifted) m a -> [a] Source

null :: Const (TYPE Lifted) m a -> Bool Source

length :: Const (TYPE Lifted) m a -> Int Source

elem :: Eq a => a -> Const (TYPE Lifted) m a -> Bool Source

maximum :: Ord a => Const (TYPE Lifted) m a -> a Source

minimum :: Ord a => Const (TYPE Lifted) m a -> a Source

sum :: Num a => Const (TYPE Lifted) m a -> a Source

product :: Num a => Const (TYPE Lifted) m a -> a Source

Traversable (Const (TYPE Lifted) m) 

Methods

traverse :: Applicative f => (a -> f b) -> Const (TYPE Lifted) m a -> f (Const (TYPE Lifted) m b) Source

sequenceA :: Applicative f => Const (TYPE Lifted) m (f a) -> f (Const (TYPE Lifted) m a) Source

mapM :: Monad m => (a -> m b) -> Const (TYPE Lifted) m a -> m (Const (TYPE Lifted) m b) Source

sequence :: Monad m => Const (TYPE Lifted) m (m a) -> m (Const (TYPE Lifted) m a) Source

Generic1 (Const (TYPE Lifted) a) 

Associated Types

type Rep1 (Const (TYPE Lifted) a :: * -> TYPE Lifted) :: * -> * Source

Methods

from1 :: Const (TYPE Lifted) a a -> Rep1 (Const (TYPE Lifted) a) a Source

to1 :: Rep1 (Const (TYPE Lifted) a) a -> Const (TYPE Lifted) a a Source

Show a => Show1 (Const (TYPE Lifted) a) 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Const (TYPE Lifted) a a -> ShowS Source

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Const (TYPE Lifted) a a] -> ShowS Source

Read a => Read1 (Const (TYPE Lifted) a) 

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Const (TYPE Lifted) a a) Source

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Const (TYPE Lifted) a a] Source

Ord a => Ord1 (Const (TYPE Lifted) a) 

Methods

liftCompare :: (a -> b -> Ordering) -> Const (TYPE Lifted) a a -> Const (TYPE Lifted) a b -> Ordering Source

Eq a => Eq1 (Const (TYPE Lifted) a) 

Methods

liftEq :: (a -> b -> Bool) -> Const (TYPE Lifted) a a -> Const (TYPE Lifted) a b -> Bool Source

Bounded a => Bounded (Const k a b) 

Methods

minBound :: Const k a b Source

maxBound :: Const k a b Source

Enum a => Enum (Const k a b) 

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) 

Methods

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

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

Ord a => Ord (Const k a b) 

Methods

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

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

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

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

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

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

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

Read a => Read (Const k a b)

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

Show a => Show (Const k a b)

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) 

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

Generic (Const k a b) 

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) 

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) 

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

Storable a => Storable (Const k a b) 

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 k 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) = D1 (MetaData "Const" "Data.Functor.Const" "base" True) (C1 (MetaCons "Const" PrefixI True) (S1 (MetaSel (Just Symbol "getConst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))