hs-ix-0.2.0.0: Indexed applicative functors and monads
Safe HaskellNone
LanguageHaskell2010

Data.Functor.Indexed.Const

Description

The indexed constant functor: a Const κ ignores its final argument and merely holds a morphism of κ, which are composed as the Const terms are joined and (<*>)d.

Documentation

newtype Const κ a b z Source #

Constructors

Const 

Fields

Instances

Instances details
Semigroupoid κ => Apply (Const κ :: k -> k -> Type -> Type) Source # 
Instance details

Defined in Data.Functor.Indexed.Const

Methods

(<*>) :: forall (i :: k0) (j :: k0) a b (k1 :: k0). Const κ i j (a -> b) -> Const κ j k1 a -> Const κ i k1 b Source #

(*>) :: forall (i :: k0) (j :: k0) a (k1 :: k0) b. Const κ i j a -> Const κ j k1 b -> Const κ i k1 b Source #

(<*) :: forall (i :: k0) (j :: k0) a (k1 :: k0) b. Const κ i j a -> Const κ j k1 b -> Const κ i k1 a Source #

liftA2 :: forall a b c (i :: k0) (j :: k0) (k1 :: k0). (a -> b -> c) -> Const κ i j a -> Const κ j k1 b -> Const κ i k1 c Source #

Functor (Const κ a b :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Indexed.Const

Methods

fmap :: (a0 -> b0) -> Const κ a b a0 -> Const κ a b b0 #

(<$) :: a0 -> Const κ a b b0 -> Const κ a b a0 #

Category κ => Applicative (Const κ a a :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Indexed.Const

Methods

pure :: a0 -> Const κ a a a0 #

(<*>) :: Const κ a a (a0 -> b) -> Const κ a a a0 -> Const κ a a b #

liftA2 :: (a0 -> b -> c) -> Const κ a a a0 -> Const κ a a b -> Const κ a a c #

(*>) :: Const κ a a a0 -> Const κ a a b -> Const κ a a b #

(<*) :: Const κ a a a0 -> Const κ a a b -> Const κ a a a0 #

Foldable (Const κ a b :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Indexed.Const

Methods

fold :: Monoid m => Const κ a b m -> m #

foldMap :: Monoid m => (a0 -> m) -> Const κ a b a0 -> m #

foldMap' :: Monoid m => (a0 -> m) -> Const κ a b a0 -> m #

foldr :: (a0 -> b0 -> b0) -> b0 -> Const κ a b a0 -> b0 #

foldr' :: (a0 -> b0 -> b0) -> b0 -> Const κ a b a0 -> b0 #

foldl :: (b0 -> a0 -> b0) -> b0 -> Const κ a b a0 -> b0 #

foldl' :: (b0 -> a0 -> b0) -> b0 -> Const κ a b a0 -> b0 #

foldr1 :: (a0 -> a0 -> a0) -> Const κ a b a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> Const κ a b a0 -> a0 #

toList :: Const κ a b a0 -> [a0] #

null :: Const κ a b a0 -> Bool #

length :: Const κ a b a0 -> Int #

elem :: Eq a0 => a0 -> Const κ a b a0 -> Bool #

maximum :: Ord a0 => Const κ a b a0 -> a0 #

minimum :: Ord a0 => Const κ a b a0 -> a0 #

sum :: Num a0 => Const κ a b a0 -> a0 #

product :: Num a0 => Const κ a b a0 -> a0 #

Traversable (Const κ a b :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Indexed.Const

Methods

traverse :: Applicative f => (a0 -> f b0) -> Const κ a b a0 -> f (Const κ a b b0) #

sequenceA :: Applicative f => Const κ a b (f a0) -> f (Const κ a b a0) #

mapM :: Monad m => (a0 -> m b0) -> Const κ a b a0 -> m (Const κ a b b0) #

sequence :: Monad m => Const κ a b (m a0) -> m (Const κ a b a0) #

Eq (κ a b) => Eq (Const κ a b z) Source # 
Instance details

Defined in Data.Functor.Indexed.Const

Methods

(==) :: Const κ a b z -> Const κ a b z -> Bool #

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

Ord (κ a b) => Ord (Const κ a b z) Source # 
Instance details

Defined in Data.Functor.Indexed.Const

Methods

compare :: Const κ a b z -> Const κ a b z -> Ordering #

(<) :: Const κ a b z -> Const κ a b z -> Bool #

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

(>) :: Const κ a b z -> Const κ a b z -> Bool #

(>=) :: Const κ a b z -> Const κ a b z -> Bool #

max :: Const κ a b z -> Const κ a b z -> Const κ a b z #

min :: Const κ a b z -> Const κ a b z -> Const κ a b z #

Show (κ a b) => Show (Const κ a b z) Source # 
Instance details

Defined in Data.Functor.Indexed.Const

Methods

showsPrec :: Int -> Const κ a b z -> ShowS #

show :: Const κ a b z -> String #

showList :: [Const κ a b z] -> ShowS #