transformers-0.6.1.1: Concrete functor and monad transformers
Copyright(c) Ross Paterson 2010
LicenseBSD-style (see the file LICENSE)
MaintainerR.Paterson@city.ac.uk
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Data.Functor.Constant

Description

The constant functor.

Synopsis

Documentation

newtype Constant a b Source #

Constant functor.

Constructors

Constant 

Fields

Instances

Instances details
Generic1 (Constant a :: k -> Type) Source # 
Instance details

Defined in Data.Functor.Constant

Associated Types

type Rep1 (Constant a) :: k -> Type #

Methods

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

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

Bifoldable (Constant :: Type -> TYPE LiftedRep -> Type) Source # 
Instance details

Defined in Data.Functor.Constant

Methods

bifold :: Monoid m => Constant m m -> m #

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

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Constant a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Constant a b -> c #

Bifunctor (Constant :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constant

Methods

bimap :: (a -> b) -> (c -> d) -> Constant a c -> Constant b d #

first :: (a -> b) -> Constant a c -> Constant b c #

second :: (b -> c) -> Constant a b -> Constant a c #

Bitraversable (Constant :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constant

Methods

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

Eq2 (Constant :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constant

Methods

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

Ord2 (Constant :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constant

Methods

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

Read2 (Constant :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constant

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Constant a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Constant a b] #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Constant a b) #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Constant a b] #

Show2 (Constant :: Type -> TYPE LiftedRep -> Type) Source # 
Instance details

Defined in Data.Functor.Constant

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Constant a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Constant a b] -> ShowS #

Foldable (Constant a :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in Data.Functor.Constant

Methods

fold :: Monoid m => Constant a m -> m #

foldMap :: Monoid m => (a0 -> m) -> Constant a a0 -> m #

foldMap' :: Monoid m => (a0 -> m) -> Constant a a0 -> m #

foldr :: (a0 -> b -> b) -> b -> Constant a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> Constant a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> Constant a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> Constant a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> Constant a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> Constant a a0 -> a0 #

toList :: Constant a a0 -> [a0] #

null :: Constant a a0 -> Bool #

length :: Constant a a0 -> Int #

elem :: Eq a0 => a0 -> Constant a a0 -> Bool #

maximum :: Ord a0 => Constant a a0 -> a0 #

minimum :: Ord a0 => Constant a a0 -> a0 #

sum :: Num a0 => Constant a a0 -> a0 #

product :: Num a0 => Constant a a0 -> a0 #

Eq a => Eq1 (Constant a :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constant

Methods

liftEq :: (a0 -> b -> Bool) -> Constant a a0 -> Constant a b -> Bool #

Ord a => Ord1 (Constant a :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constant

Methods

liftCompare :: (a0 -> b -> Ordering) -> Constant a a0 -> Constant a b -> Ordering #

Read a => Read1 (Constant a :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constant

Methods

liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Constant a a0) #

liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Constant a a0] #

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Constant a a0) #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Constant a a0] #

Show a => Show1 (Constant a :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in Data.Functor.Constant

Methods

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

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

Contravariant (Constant a :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constant

Methods

contramap :: (a' -> a0) -> Constant a a0 -> Constant a a' #

(>$) :: b -> Constant a b -> Constant a a0 #

Traversable (Constant a :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constant

Methods

traverse :: Applicative f => (a0 -> f b) -> Constant a a0 -> f (Constant a b) #

sequenceA :: Applicative f => Constant a (f a0) -> f (Constant a a0) #

mapM :: Monad m => (a0 -> m b) -> Constant a a0 -> m (Constant a b) #

sequence :: Monad m => Constant a (m a0) -> m (Constant a a0) #

Monoid a => Applicative (Constant a :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constant

Methods

pure :: a0 -> Constant a a0 #

(<*>) :: Constant a (a0 -> b) -> Constant a a0 -> Constant a b #

liftA2 :: (a0 -> b -> c) -> Constant a a0 -> Constant a b -> Constant a c #

(*>) :: Constant a a0 -> Constant a b -> Constant a b #

(<*) :: Constant a a0 -> Constant a b -> Constant a a0 #

Functor (Constant a :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constant

Methods

fmap :: (a0 -> b) -> Constant a a0 -> Constant a b #

(<$) :: a0 -> Constant a b -> Constant a a0 #

(Typeable b, Typeable k, Data a) => Data (Constant a b) Source # 
Instance details

Defined in Data.Functor.Constant

Methods

gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Constant a b -> c (Constant a b) #

gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Constant a b) #

toConstr :: Constant a b -> Constr #

dataTypeOf :: Constant a b -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Constant a b)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Constant a b)) #

gmapT :: (forall b0. Data b0 => b0 -> b0) -> Constant a b -> Constant a b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Constant a b -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Constant a b -> r #

gmapQ :: (forall d. Data d => d -> u) -> Constant a b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Constant a b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Constant a b -> m (Constant a b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Constant a b -> m (Constant a b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Constant a b -> m (Constant a b) #

Monoid a => Monoid (Constant a b) Source # 
Instance details

Defined in Data.Functor.Constant

Methods

mempty :: Constant a b #

mappend :: Constant a b -> Constant a b -> Constant a b #

mconcat :: [Constant a b] -> Constant a b #

Semigroup a => Semigroup (Constant a b) Source # 
Instance details

Defined in Data.Functor.Constant

Methods

(<>) :: Constant a b -> Constant a b -> Constant a b #

sconcat :: NonEmpty (Constant a b) -> Constant a b #

stimes :: Integral b0 => b0 -> Constant a b -> Constant a b #

Generic (Constant a b) Source # 
Instance details

Defined in Data.Functor.Constant

Associated Types

type Rep (Constant a b) :: Type -> Type #

Methods

from :: Constant a b -> Rep (Constant a b) x #

to :: Rep (Constant a b) x -> Constant a b #

Read a => Read (Constant a b) Source # 
Instance details

Defined in Data.Functor.Constant

Show a => Show (Constant a b) Source # 
Instance details

Defined in Data.Functor.Constant

Methods

showsPrec :: Int -> Constant a b -> ShowS #

show :: Constant a b -> String #

showList :: [Constant a b] -> ShowS #

Eq a => Eq (Constant a b) Source # 
Instance details

Defined in Data.Functor.Constant

Methods

(==) :: Constant a b -> Constant a b -> Bool #

(/=) :: Constant a b -> Constant a b -> Bool #

Ord a => Ord (Constant a b) Source # 
Instance details

Defined in Data.Functor.Constant

Methods

compare :: Constant a b -> Constant a b -> Ordering #

(<) :: Constant a b -> Constant a b -> Bool #

(<=) :: Constant a b -> Constant a b -> Bool #

(>) :: Constant a b -> Constant a b -> Bool #

(>=) :: Constant a b -> Constant a b -> Bool #

max :: Constant a b -> Constant a b -> Constant a b #

min :: Constant a b -> Constant a b -> Constant a b #

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

Defined in Data.Functor.Constant

type Rep1 (Constant a :: k -> Type) = D1 ('MetaData "Constant" "Data.Functor.Constant" "transformers-0.6.1.1-DxZFGURZdTFOo983wl5oD" 'True) (C1 ('MetaCons "Constant" 'PrefixI 'True) (S1 ('MetaSel ('Just "getConstant") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
type Rep (Constant a b) Source # 
Instance details

Defined in Data.Functor.Constant

type Rep (Constant a b) = D1 ('MetaData "Constant" "Data.Functor.Constant" "transformers-0.6.1.1-DxZFGURZdTFOo983wl5oD" 'True) (C1 ('MetaCons "Constant" 'PrefixI 'True) (S1 ('MetaSel ('Just "getConstant") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))