Safe Haskell | None |
---|---|
Language | Haskell98 |
This module provides a type-indexed / parameterized version of the Functor
and Applicative
classes.
Synopsis
- class IndexedFunctor f where
- imap :: (x -> y) -> (a -> b) -> f x a -> f y b
- class IndexedFunctor f => IndexedApplicative f where
- (<<$>>) :: IndexedFunctor f => (a -> b) -> f y a -> f y b
- (<<**>>) :: IndexedApplicative f => f x a -> f (x -> y) (a -> b) -> f y b
- liftIA :: IndexedApplicative f => (a -> b) -> (x -> y) -> f a x -> f b y
- liftIA2 :: IndexedApplicative f => (a -> b -> c) -> (x -> y -> z) -> f a x -> f b y -> f c z
- liftIA3 :: IndexedApplicative f => (a -> b -> c -> d) -> (w -> x -> y -> z) -> f a w -> f b x -> f c y -> f d z
- newtype WrappedApplicative f index a = WrappedApplicative {
- unwrapApplicative :: f a
type-indexed / parameterized classes
class IndexedFunctor f where Source #
a class for a 'type-indexed' or paramaterized
functor
note: not sure what the most correct name is for this class, or if it exists in a well supported library already.
:: (x -> y) | function to apply to first parameter |
-> (a -> b) | function to apply to second parameter |
-> f x a | indexed functor |
-> f y b |
imap is similar to fmap
Instances
Functor f => IndexedFunctor (WrappedApplicative f) Source # | |
Defined in Control.Applicative.Indexed imap :: (x -> y) -> (a -> b) -> WrappedApplicative f x a -> WrappedApplicative f y b Source # | |
Monad m => IndexedFunctor (Form m input view error) Source # | |
class IndexedFunctor f => IndexedApplicative f where Source #
a class for a 'type-indexed' or paramaterized
applicative functors
note: not sure what the most correct name is for this class, or if it exists in a well supported library already.
ipure :: x -> a -> f x a Source #
similar to pure
(<<*>>) :: f (x -> y) (a -> b) -> f x a -> f y b infixl 4 Source #
similar to <*>
(*>>) :: f x a -> f y b -> f y b infixl 4 Source #
similar to *>
(<<*) :: f x a -> f y b -> f x a infixl 4 Source #
similar to <*
Instances
Applicative f => IndexedApplicative (WrappedApplicative f) Source # | |
Defined in Control.Applicative.Indexed ipure :: x -> a -> WrappedApplicative f x a Source # (<<*>>) :: WrappedApplicative f (x -> y) (a -> b) -> WrappedApplicative f x a -> WrappedApplicative f y b Source # (*>>) :: WrappedApplicative f x a -> WrappedApplicative f y b -> WrappedApplicative f y b Source # (<<*) :: WrappedApplicative f x a -> WrappedApplicative f y b -> WrappedApplicative f x a Source # | |
(Monoid view, Monad m) => IndexedApplicative (Form m input error view) Source # | |
Defined in Text.Reform.Core ipure :: x -> a -> Form m input error view x a Source # (<<*>>) :: Form m input error view (x -> y) (a -> b) -> Form m input error view x a -> Form m input error view y b Source # (*>>) :: Form m input error view x a -> Form m input error view y b -> Form m input error view y b Source # (<<*) :: Form m input error view x a -> Form m input error view y b -> Form m input error view x a Source # |
(<<$>>) :: IndexedFunctor f => (a -> b) -> f y a -> f y b infixl 4 Source #
similar to <$>
. An alias for imap id
(<<**>>) :: IndexedApplicative f => f x a -> f (x -> y) (a -> b) -> f y b Source #
A variant of <<*>>
with the arguments reversed.
liftIA :: IndexedApplicative f => (a -> b) -> (x -> y) -> f a x -> f b y Source #
Lift a function to actions.
This function may be used as a value for imap
in a IndexedFunctor
instance.
liftIA2 :: IndexedApplicative f => (a -> b -> c) -> (x -> y -> z) -> f a x -> f b y -> f c z Source #
Lift a binary function to actions.
liftIA3 :: IndexedApplicative f => (a -> b -> c -> d) -> (w -> x -> y -> z) -> f a w -> f b x -> f c y -> f d z Source #
Lift a binary function to actions.
WrappedApplicative
newtype WrappedApplicative f index a Source #
a wrapper which lifts a value with an Applicative
instance so that it can be used as an IndexedFunctor
or IndexedApplicative
d :: WrappedApplicative Maybe y Char d = WrappedApplicative (Just succ) <<*>> WrappedApplicative (Just 'c')