| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
MultiInstance
Description
The MultiInstance module provides alternative versions of common typeclasses,
augmented with a phantom type parameter x. The purpose of this is to deal with
the case where a type has more than one candidate instance for the original,
unaugmented class.
Example: Integer sum and product
The canonical example of this predicament is selecting the monoid instance for a
type which forms a ring (and thus has at least two strong candidates for
selection as the monoid), such as Integer. This therefore gives rise to the
Sum and Product newtype wrappers, corresponding to
the additive and multiplicative monoids respectively.
The traditional fold-based summation of a list of integers
looks like this:
>>>import Data.Foldable (fold)>>>import Data.Monoid (Sum (..))>>>getSum (fold [Sum 2, Sum 3, Sum 5]) :: Integer10
By replacing fold with multi'fold, whose constraint is
MultiMonoid rather than Monoid, we can write the same thing
without the newtype wrapper:
>>>:set -XFlexibleContexts -XTypeApplications>>>multi'fold @Addition [2, 3, 5] :: Integer10
The typeclasses
The current list of "multi-instance" typeclasses:
The phantom types
The current list of phantom types used for the x type parameter:
DefaultConjunctionDisjunctionAddition(alias forDisjunction)Multiplication(alias forConjunction)And(alias forConjunction)Or(alias forDisjunction)MinMaxMinMaybeMaxMaybeFirstLastArrowCompositionMultiDual
Synopsis
- class MultiSemigroup x a where
- multi'append :: a -> a -> a
- multi'sconcat :: NonEmpty a -> a
- multi'stimes :: Integral b => b -> a -> a
- class MultiSemigroup x a => MultiMonoid x a where
- multi'empty :: a
- multi'mconcat :: [a] -> a
- data Default
- data Conjunction
- data Disjunction
- type Addition = Disjunction
- type Multiplication = Conjunction
- multi'sum :: (Foldable t, MultiMonoid Addition a) => t a -> a
- multi'product :: (Foldable t, MultiMonoid Multiplication a) => t a -> a
- type And = Conjunction
- type Or = Disjunction
- multi'and :: (Foldable t, MultiMonoid And a) => t a -> a
- multi'or :: (Foldable t, MultiMonoid Or a) => t a -> a
- multi'any :: (Foldable t, MultiMonoid Or b) => (a -> b) -> t a -> b
- multi'all :: Foldable t => (a -> Bool) -> t a -> Bool
- data Min
- data Max
- data MinMaybe
- data MaxMaybe
- data First
- data Last
- data ArrowComposition
- data MultiDual a
- multi'fold :: forall x t m. (MultiMonoid x m, Foldable t) => t m -> m
- multi'foldMap :: forall x t m a. (MultiMonoid x m, Foldable t) => (a -> m) -> t a -> m
- multi'find :: Foldable t => (a -> Bool) -> t a -> Maybe a
Semigroup
class MultiSemigroup x a where Source #
Akin to the Semigroup class, but with the addition of the
phantom type parameter x which lets you specify which semigroup to use.
For example, the integers form a semigroup via either Addition or
Multiplication:
>>>:set -XFlexibleContexts -XTypeApplications>>>multi'append @Addition 6 7 :: Integer13>>>multi'append @Multiplication 6 7 :: Integer42>>>multi'stimes @Addition (3 :: Natural) (4 :: Integer)12>>>multi'stimes @Multiplication (3 :: Natural) (4 :: Integer)64
Minimal complete definition
Methods
multi'append :: a -> a -> a Source #
An associative operation.
Akin to <>.
multi'sconcat :: NonEmpty a -> a Source #
Reduce a non-empty list with multi'append.
Akin to sconcat.
multi'stimes :: Integral b => b -> a -> a Source #
Repeat a value n times.
Akin to stimes.
Instances
Monoid
class MultiSemigroup x a => MultiMonoid x a where Source #
Akin to the Monoid class, but with the addition of the
phantom type parameter x which lets you specify which monoid to use.
For example, the integers form a monoid via either Addition or
Multiplication:
>>>:set -XFlexibleContexts -XTypeApplications>>>multi'fold @Addition [] :: Integer0>>>multi'fold @Addition [2, 3, 5] :: Integer10>>>multi'fold @Multiplication [] :: Integer1>>>multi'fold @Multiplication [2, 3, 5] :: Integer30
Minimal complete definition
Methods
multi'empty :: a Source #
Identity of multi'append.
Akin to mempty.
multi'mconcat :: [a] -> a Source #
Fold a list using the monoid.
Akin to mconcat.
Instances
Default
Instances
| (Semigroup a, Monoid a) => MultiMonoid Default a Source # | |
Defined in MultiInstance | |
| Semigroup a => MultiSemigroup Default a Source # | |
Defined in MultiInstance Methods multi'append :: a -> a -> a Source # multi'sconcat :: NonEmpty a -> a Source # multi'stimes :: Integral b => b -> a -> a Source # | |
Conjunction and disjunction
data Conjunction Source #
Instances
| MultiMonoid Multiplication Int Source # | |
Defined in MultiInstance | |
| MultiMonoid Multiplication Integer Source # | |
Defined in MultiInstance | |
| MultiMonoid Multiplication Natural Source # | |
Defined in MultiInstance | |
| MultiMonoid And Bool Source # | |
Defined in MultiInstance | |
| MultiSemigroup Multiplication Int Source # | |
Defined in MultiInstance | |
| MultiSemigroup Multiplication Integer Source # | |
Defined in MultiInstance | |
| MultiSemigroup Multiplication Natural Source # | |
Defined in MultiInstance | |
| MultiSemigroup And Bool Source # | |
Defined in MultiInstance | |
data Disjunction Source #
Instances
| MultiMonoid Addition Int Source # | |
Defined in MultiInstance | |
| MultiMonoid Addition Integer Source # | |
Defined in MultiInstance | |
| MultiMonoid Addition Natural Source # | |
Defined in MultiInstance | |
| MultiMonoid Or Bool Source # | |
Defined in MultiInstance | |
| MultiSemigroup Addition Int Source # | |
Defined in MultiInstance | |
| MultiSemigroup Addition Integer Source # | |
Defined in MultiInstance | |
| MultiSemigroup Addition Natural Source # | |
Defined in MultiInstance | |
| MultiSemigroup Or Bool Source # | |
Defined in MultiInstance | |
| MultiMonoid Addition [a] Source # | |
Defined in MultiInstance | |
| MultiSemigroup Addition [a] Source # | |
Defined in MultiInstance Methods multi'append :: [a] -> [a] -> [a] Source # multi'sconcat :: NonEmpty [a] -> [a] Source # multi'stimes :: Integral b => b -> [a] -> [a] Source # | |
| MultiSemigroup Addition (NonEmpty a) Source # | |
Defined in MultiInstance | |
Addition and multiplication
type Addition = Disjunction Source #
type Multiplication = Conjunction Source #
multi'product :: (Foldable t, MultiMonoid Multiplication a) => t a -> a Source #
Boolean and and or
type And = Conjunction Source #
type Or = Disjunction Source #
multi'any :: (Foldable t, MultiMonoid Or b) => (a -> b) -> t a -> b Source #
Determines whether any element of the structure satisfies the predicate.
Equivalent to .multi'foldMap @Or
Akin to any.
multi'all :: Foldable t => (a -> Bool) -> t a -> Bool Source #
Determines whether all elements of the structure satisfy the predicate.
Equivalent to .multi'foldMap @And
Akin to all.
Min and max
Instances
| Ord a => MultiSemigroup Min a Source # | |
Defined in MultiInstance Methods multi'append :: a -> a -> a Source # multi'sconcat :: NonEmpty a -> a Source # multi'stimes :: Integral b => b -> a -> a Source # | |
Instances
| Ord a => MultiSemigroup Max a Source # | |
Defined in MultiInstance Methods multi'append :: a -> a -> a Source # multi'sconcat :: NonEmpty a -> a Source # multi'stimes :: Integral b => b -> a -> a Source # | |
Instances
| Ord a => MultiMonoid MinMaybe (Maybe a) Source # | |
Defined in MultiInstance | |
| Ord a => MultiSemigroup MinMaybe (Maybe a) Source # | |
Defined in MultiInstance | |
Instances
| Ord a => MultiMonoid MaxMaybe (Maybe a) Source # | |
Defined in MultiInstance | |
| Ord a => MultiSemigroup MaxMaybe (Maybe a) Source # | |
Defined in MultiInstance | |
First and last
Instances
| MultiMonoid First (Maybe a) Source # | |
Defined in MultiInstance | |
| MultiSemigroup First (Maybe a) Source # | |
Defined in MultiInstance | |
Instances
| MultiMonoid Last (Maybe a) Source # | |
Defined in MultiInstance | |
| MultiSemigroup Last (Maybe a) Source # | |
Defined in MultiInstance | |
Arrow composition
data ArrowComposition Source #
Instances
| MultiMonoid ArrowComposition (a -> a) Source # | |
Defined in MultiInstance | |
| MultiSemigroup ArrowComposition (a -> a) Source # | |
Defined in MultiInstance Methods multi'append :: (a -> a) -> (a -> a) -> a -> a Source # multi'sconcat :: NonEmpty (a -> a) -> a -> a Source # multi'stimes :: Integral b => b -> (a -> a) -> a -> a Source # | |
| Monad m => MultiMonoid ArrowComposition (Kleisli m a a) Source # | |
Defined in MultiInstance Methods multi'empty :: Kleisli m a a Source # multi'mconcat :: [Kleisli m a a] -> Kleisli m a a Source # | |
| Monad m => MultiSemigroup ArrowComposition (Kleisli m a a) Source # | |
Defined in MultiInstance | |
Dual
Instances
| MultiMonoid x a => MultiMonoid (MultiDual x) a Source # | |
Defined in MultiInstance | |
| MultiSemigroup x a => MultiSemigroup (MultiDual x) a Source # | |
Defined in MultiInstance Methods multi'append :: a -> a -> a Source # multi'sconcat :: NonEmpty a -> a Source # multi'stimes :: Integral b => b -> a -> a Source # | |
Monoidal folds
multi'fold :: forall x t m. (MultiMonoid x m, Foldable t) => t m -> m Source #
Combine the elements of a structure using a monoid.
Akin to fold.
multi'foldMap :: forall x t m a. (MultiMonoid x m, Foldable t) => (a -> m) -> t a -> m Source #
Map each element of the structure to a monoid, and combine the results.
Akin to foldMap.