Copyright | (c) Ross Paterson 2010 |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | R.Paterson@city.ac.uk |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
The constant functor.
Synopsis
- newtype Constant a b = Constant {
- getConstant :: a
Documentation
Constant functor.
Constant | |
|
Instances
Generic1 (Constant a :: k -> Type) Source # | |
Bifoldable (Constant :: Type -> TYPE LiftedRep -> Type) Source # | |
Bifunctor (Constant :: Type -> Type -> Type) Source # | |
Bitraversable (Constant :: Type -> Type -> Type) Source # | |
Defined in Data.Functor.Constant bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Constant a b -> f (Constant c d) # | |
Eq2 (Constant :: Type -> Type -> Type) Source # | |
Ord2 (Constant :: Type -> Type -> Type) Source # | |
Defined in Data.Functor.Constant | |
Read2 (Constant :: Type -> Type -> Type) Source # | |
Defined in Data.Functor.Constant 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 # | |
Foldable (Constant a :: TYPE LiftedRep -> Type) Source # | |
Defined in Data.Functor.Constant 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 # | |
Eq a => Eq1 (Constant a :: Type -> Type) Source # | |
Ord a => Ord1 (Constant a :: Type -> Type) Source # | |
Defined in Data.Functor.Constant | |
Read a => Read1 (Constant a :: Type -> Type) Source # | |
Defined in Data.Functor.Constant 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 # | |
Contravariant (Constant a :: Type -> Type) Source # | |
Traversable (Constant a :: Type -> Type) Source # | |
Defined in Data.Functor.Constant | |
Monoid a => Applicative (Constant a :: Type -> Type) Source # | |
Defined in Data.Functor.Constant | |
Functor (Constant a :: Type -> Type) Source # | |
(Typeable b, Typeable k, Data a) => Data (Constant a b) Source # | |
Defined in Data.Functor.Constant 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 # | |
Semigroup a => Semigroup (Constant a b) Source # | |
Generic (Constant a b) Source # | |
Read a => Read (Constant a b) Source # | |
Show a => Show (Constant a b) Source # | |
Eq a => Eq (Constant a b) Source # | |
Ord a => Ord (Constant a b) Source # | |
Defined in Data.Functor.Constant | |
type Rep1 (Constant a :: k -> Type) Source # | |
Defined in Data.Functor.Constant | |
type Rep (Constant a b) Source # | |
Defined in Data.Functor.Constant |