| Copyright | (c) Andrey Mokhov 2018-2023 | 
|---|---|
| License | MIT (see the file LICENSE) | 
| Maintainer | andrey.mokhov@gmail.com | 
| Stability | experimental | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Control.Selective
Description
This is a library for selective applicative functors, or just selective functors for short, an abstraction between applicative functors and monads, introduced in this paper: https://www.staff.ncl.ac.uk/andrey.mokhov/selective-functors.pdf.
Synopsis
- class Applicative f => Selective f where
- (<*?) :: Selective f => f (Either a b) -> f (a -> b) -> f b
- branch :: Selective f => f (Either a b) -> f (a -> c) -> f (b -> c) -> f c
- selectA :: Applicative f => f (Either a b) -> f (a -> b) -> f b
- selectT :: Traversable f => f (Either a b) -> f (a -> b) -> f b
- apS :: Selective f => f (a -> b) -> f a -> f b
- selectM :: Monad f => f (Either a b) -> f (a -> b) -> f b
- ifS :: Selective f => f Bool -> f a -> f a -> f a
- whenS :: Selective f => f Bool -> f () -> f ()
- fromMaybeS :: Selective f => f a -> f (Maybe a) -> f a
- orElse :: (Selective f, Semigroup e) => f (Either e a) -> f (Either e a) -> f (Either e a)
- andAlso :: (Selective f, Semigroup a) => f (Either e a) -> f (Either e a) -> f (Either e a)
- untilRight :: (Monoid a, Selective f) => f (Either a b) -> f (a, b)
- whileS :: Selective f => f Bool -> f ()
- (<||>) :: Selective f => f Bool -> f Bool -> f Bool
- (<&&>) :: Selective f => f Bool -> f Bool -> f Bool
- foldS :: (Selective f, Foldable t, Monoid a) => t (f (Either e a)) -> f (Either e a)
- anyS :: Selective f => (a -> f Bool) -> [a] -> f Bool
- allS :: Selective f => (a -> f Bool) -> [a] -> f Bool
- bindS :: (Bounded a, Enum a, Eq a, Selective f) => f a -> (a -> f b) -> f b
- data Cases a
- casesEnum :: (Bounded a, Enum a) => Cases a
- cases :: Eq a => [a] -> Cases a
- matchS :: (Eq a, Selective f) => Cases a -> f a -> (a -> f b) -> f (Either a b)
- matchM :: Monad m => Cases a -> m a -> (a -> m b) -> m (Either a b)
- newtype SelectA f a = SelectA {- getSelectA :: f a
 
- newtype SelectM f a = SelectM {- getSelectM :: f a
 
- newtype Over m a = Over {- getOver :: m
 
- newtype Under m a = Under {- getUnder :: m
 
- data Validation e a
- swapEither :: Either a b -> Either b a
- newtype ComposeEither f e a = ComposeEither (f (Either e a))
- newtype ComposeTraversable f g a = ComposeTraversable (f (g a))
Type class
class Applicative f => Selective f where Source #
Selective applicative functors. You can think of select as a selective
 function application: when given a value of type Left a, you must apply
 the given function, but when given a Right b, you may skip the
 function and associated effects, and simply return the b.
Note that it is not a requirement for selective functors to skip unnecessary effects. It may be counterintuitive, but this makes them more useful. Why? Typically, when executing a selective computation, you would want to skip the effects (saving work); but on the other hand, if your goal is to statically analyse a given selective computation and extract the set of all possible effects (without actually executing them), then you do not want to skip any effects, because that defeats the purpose of static analysis.
The type signature of select is reminiscent of both <*> and >>=, and
 indeed a selective functor is in some sense a composition of an applicative
 functor and the Either monad.
Laws:
- Identity:
x <*? pure id = either id id <$> x
- Distributivity; note that yandzhave the same typef (a -> b):
pure x <*? (y *> z) = (pure x <*? y) *> (pure x <*? z)
- Associativity:
x <*? (y <*? z) = (f <$> x) <*? (g <$> y) <*? (h <$> z)
  where
    f x = Right <$> x
    g y = a -> bimap (,a) ($a) y
    h z = uncurry z
- Monadic select(for selective functors that are also monads):
select = selectM
There are also a few useful theorems:
- Apply a pure function to the result:
f <$> select x y = select (fmap f <$> x) (fmap f <$> y)
- Apply a pure function to the Leftcase of the first argument:
select (first f <$> x) y = select x ((. f) <$> y)
- Apply a pure function to the second argument:
select x (f <$> y) = select (first (flip f) <$> x) ((&) <$> y)
- Generalised identity:
x <*? pure y = either y id <$> x
- A selective functor is rigid if it satisfies <*>=apS. The following interchange law holds for rigid selective functors:
x *> (y <*? z) = (x *> y) <*? z
If f is also a Monad, we require that select = selectM, from which one
 can prove <*> = apS.
Instances
(<*?) :: Selective f => f (Either a b) -> f (a -> b) -> f b infixl 4 Source #
An operator alias for select, which is sometimes convenient. It tries to
 follow the notational convention for Applicative operators. The angle
 bracket pointing to the left means we always use the corresponding value.
 The value on the right, however, may be skipped, hence the question mark.
branch :: Selective f => f (Either a b) -> f (a -> c) -> f (b -> c) -> f c Source #
The branch function is a natural generalisation of select: instead of
 skipping an unnecessary effect, it chooses which of the two given effectful
 functions to apply to a given argument; the other effect is unnecessary. It
 is possible to implement branch in terms of select, which is a good
 puzzle (give it a try!).
We can also implement select via branch:
selectB :: Selective f => f (Either a b) -> f (a -> b) -> f b selectB x y = branch x y (pure id)
selectA :: Applicative f => f (Either a b) -> f (a -> b) -> f b Source #
We can write a function with the type signature of select using the
 Applicative type class, but it will always execute the effects associated
 with the second argument, hence being potentially less efficient.
selectT :: Traversable f => f (Either a b) -> f (a -> b) -> f b Source #
apS :: Selective f => f (a -> b) -> f a -> f b Source #
Recover the application operator <*> from select. Rigid selective
functors satisfy the law <*> = apS and furthermore, the resulting
applicative functor satisfies all laws of Applicative:
- Identity: - pure id <*> v = v 
- Homomorphism: - pure f <*> pure x = pure (f x) 
- Interchange: - u <*> pure y = pure ($y) <*> u 
- Composition: - (.) <$> u <*> v <*> w = u <*> (v <*> w) 
Conditional combinators
ifS :: Selective f => f Bool -> f a -> f a -> f a Source #
Branch on a Boolean value, skipping unnecessary effects.
orElse :: (Selective f, Semigroup e) => f (Either e a) -> f (Either e a) -> f (Either e a) Source #
Return the first Right value. If both are Left's, accumulate errors.
andAlso :: (Selective f, Semigroup a) => f (Either e a) -> f (Either e a) -> f (Either e a) Source #
Accumulate the Right values, or return the first Left.
untilRight :: (Monoid a, Selective f) => f (Either a b) -> f (a, b) Source #
Keep running an effectful computation until it returns a Right value,
 collecting the Left's using a supplied Monoid instance.
whileS :: Selective f => f Bool -> f () Source #
Keep checking an effectful condition while it holds.
foldS :: (Selective f, Foldable t, Monoid a) => t (f (Either e a)) -> f (Either e a) Source #
Generalised folding with the short-circuiting behaviour.
anyS :: Selective f => (a -> f Bool) -> [a] -> f Bool Source #
A lifted version of any. Retains the short-circuiting behaviour.
allS :: Selective f => (a -> f Bool) -> [a] -> f Bool Source #
A lifted version of all. Retains the short-circuiting behaviour.
casesEnum :: (Bounded a, Enum a) => Cases a Source #
The list of all possible values of an enumerable data type.
matchS :: (Eq a, Selective f) => Cases a -> f a -> (a -> f b) -> f (Either a b) Source #
Eliminate all specified values a from f (Either a b) by replacing each
 of them with a given f a.
matchM :: Monad m => Cases a -> m a -> (a -> m b) -> m (Either a b) Source #
Eliminate all specified values a from f (Either a b) by replacing each
 of them with a given f a.
Selective functors
Any applicative functor can be given a Selective instance by defining
 select = selectA. This data type captures this pattern, so you can use
 it in combination with the DerivingVia extension as follows:
newtype Over m a = Over m
    deriving (Functor, Applicative, Selective) via SelectA (Const m)
Constructors
| SelectA | |
| Fields 
 | |
Instances
| Applicative f => Applicative (SelectA f) Source # | |
| Functor f => Functor (SelectA f) Source # | |
| Applicative f => Selective (SelectA f) Source # | |
Any monad can be given a Selective instance by defining
 select = selectM. This data type captures this pattern, so you can use
 it in combination with the DerivingVia extension as follows:
newtype V1 a = V1 a
    deriving (Functor, Applicative, Selective, Monad) via SelectM Identity
Constructors
| SelectM | |
| Fields 
 | |
Static analysis of selective functors with over-approximation.
Static analysis of selective functors with under-approximation.
Instances
| Foldable (Under m) Source # | |
| Defined in Control.Selective Methods fold :: Monoid m0 => Under m m0 -> m0 # foldMap :: Monoid m0 => (a -> m0) -> Under m a -> m0 # foldMap' :: Monoid m0 => (a -> m0) -> Under m a -> m0 # foldr :: (a -> b -> b) -> b -> Under m a -> b # foldr' :: (a -> b -> b) -> b -> Under m a -> b # foldl :: (b -> a -> b) -> b -> Under m a -> b # foldl' :: (b -> a -> b) -> b -> Under m a -> b # foldr1 :: (a -> a -> a) -> Under m a -> a # foldl1 :: (a -> a -> a) -> Under m a -> a # elem :: Eq a => a -> Under m a -> Bool # maximum :: Ord a => Under m a -> a # minimum :: Ord a => Under m a -> a # | |
| Traversable (Under m) Source # | |
| Monoid m => Applicative (Under m) Source # | |
| Functor (Under m) Source # | |
| Monoid m => Selective (Under m) Source # | |
| Show m => Show (Under m a) Source # | |
| Eq m => Eq (Under m a) Source # | |
| Ord m => Ord (Under m a) Source # | |
data Validation e a Source #
Selective instance for the standard applicative functor Validation. This is a good example of a non-trivial selective functor which is not a monad.
Instances
Miscellaneous
swapEither :: Either a b -> Either b a Source #
Swap Left and Right.
newtype ComposeEither f e a Source #
Composition of a selective functor f with the Either monad.
Constructors
| ComposeEither (f (Either e a)) | 
Instances
newtype ComposeTraversable f g a Source #
Composition of a selective functor f and an applicative traversable
 functor g.
Constructors
| ComposeTraversable (f (g a)) |