| Safe Haskell | None |
|---|---|
| Language | GHC2021 |
Control.Additive
Description
This module defines a variant of the Alternative and
MonadPlus type class. Thanks to quantified constraints,
there's really nothing preventing us, in modern Haskell, to define it once
and for all at every arity.
Effectively, this is just a clone of the Monoid type class. The reason for
preferring to define another class is that applicatives have a natural Monoid
instance:
instance (Applicative f, Monoid a) => Monoid (f a) where mempty = pure mempty (<>) = liftA2 (<>)
In Base, the Monoid instances for ST, IO, and STM are defined like
this, and that of and Maybe a are of a similar nature. See also
Const a bAp.
So we typically want a second one. An approach would be to give a monoid
instance to a newtype-wrapped version of our functor gadget. But that's very
syntactically heave (see Adding, below, though). So instead we propose a
dedicated type class, named after the fact that Alternative function have
an additive flavour to them (msum, etc…), and situated in the Control
hierarchy to represent that it's intended to represent choice between
computations.
Documentation
class Additive a where Source #
Instances
| Monoid a => Additive (Monoidaly a) Source # | |
| Alternative f => Additive (Alternatively f a) Source # | |
Defined in Control.Additive Methods empty :: Alternatively f a Source # (<|>) :: Alternatively f a -> Alternatively f a -> Alternatively f a Source # | |
| Additive (Cont2W w r r' a) Source # | |
| Alternative m => Additive (IgnoreIndices m r r' a) Source # | |
Defined in Control.Monad.Indexed Methods empty :: IgnoreIndices m r r' a Source # (<|>) :: IgnoreIndices m r r' a -> IgnoreIndices m r r' a -> IgnoreIndices m r r' a Source # | |
| (Additive (f r r' a), Additive (g r r' a)) => Additive ((f :*: g) r r' a) Source # | |
Additives as monoids
Constructors
| Adding a |
Deriving-via combinators
newtype Alternatively (f :: k -> Type) (a :: k) Source #
Derive Additive instances with deriving via
Constructors
| Alternatively (f a) |
Instances
| Alternative f => Additive (Alternatively f a) Source # | |
Defined in Control.Additive Methods empty :: Alternatively f a Source # (<|>) :: Alternatively f a -> Alternatively f a -> Alternatively f a Source # | |