multi-instance-0.0.0.2: Typeclasses augmented with a phantom type parameter

Safe HaskellSafe
LanguageHaskell2010

MultiInstance

Contents

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]) :: Integer
10

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] :: Integer
10

The typeclasses

The current list of "multi-instance" typeclasses:

The phantom types

The current list of phantom types used for the x type parameter:

Synopsis

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 :: Integer
13
>>> multi'append @Multiplication 6 7 :: Integer
42
>>> multi'stimes @Addition (3 :: Natural) (4 :: Integer)
12
>>> multi'stimes @Multiplication (3 :: Natural) (4 :: Integer)
64

Minimal complete definition

multi'append

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

MultiSemigroup x () Source # 

Methods

multi'append :: () -> () -> () Source #

multi'sconcat :: NonEmpty () -> () Source #

multi'stimes :: Integral b => b -> () -> () Source #

Ord a => MultiSemigroup Max a Source # 

Methods

multi'append :: a -> a -> a Source #

multi'sconcat :: NonEmpty a -> a Source #

multi'stimes :: Integral b => b -> a -> a Source #

Ord a => MultiSemigroup Min a Source # 

Methods

multi'append :: a -> a -> a Source #

multi'sconcat :: NonEmpty a -> a Source #

multi'stimes :: Integral b => b -> a -> a Source #

MultiSemigroup Multiplication Int Source # 
MultiSemigroup Multiplication Integer Source # 
MultiSemigroup Multiplication Natural Source # 
MultiSemigroup Addition Int Source # 
MultiSemigroup Addition Integer Source # 
MultiSemigroup Addition Natural Source # 
MultiSemigroup Or Bool Source # 
MultiSemigroup And Bool Source # 
Semigroup a => MultiSemigroup Default a Source # 

Methods

multi'append :: a -> a -> a Source #

multi'sconcat :: NonEmpty a -> a Source #

multi'stimes :: Integral b => b -> a -> a Source #

MultiSemigroup Last (Maybe a) Source # 
MultiSemigroup First (Maybe a) Source # 
Ord a => MultiSemigroup MaxMaybe (Maybe a) Source # 
Ord a => MultiSemigroup MinMaybe (Maybe a) Source # 
MultiSemigroup Addition [a] Source # 

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 # 
MultiSemigroup ArrowComposition (a -> a) Source # 

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 => MultiSemigroup ArrowComposition (Kleisli m a a) Source # 

Methods

multi'append :: Kleisli m a a -> Kleisli m a a -> Kleisli m a a Source #

multi'sconcat :: NonEmpty (Kleisli m a a) -> Kleisli m a a Source #

multi'stimes :: Integral b => b -> Kleisli m a a -> Kleisli m a a Source #

MultiSemigroup x a => MultiSemigroup (MultiDual x) a Source # 

Methods

multi'append :: a -> a -> a Source #

multi'sconcat :: NonEmpty a -> a Source #

multi'stimes :: Integral b => b -> a -> a Source #

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 [] :: Integer
0
>>> multi'fold @Addition [2, 3, 5] :: Integer
10
>>> multi'fold @Multiplication [] :: Integer
1
>>> multi'fold @Multiplication [2, 3, 5] :: Integer
30

Minimal complete definition

multi'empty

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

MultiMonoid x () Source # 

Methods

multi'empty :: () Source #

multi'mconcat :: [()] -> () Source #

MultiMonoid Multiplication Int Source # 
MultiMonoid Multiplication Integer Source # 
MultiMonoid Multiplication Natural Source # 
MultiMonoid Addition Int Source # 
MultiMonoid Addition Integer Source # 
MultiMonoid Addition Natural Source # 
MultiMonoid Or Bool Source # 
MultiMonoid And Bool Source # 
(Semigroup a, Monoid a) => MultiMonoid Default a Source # 

Methods

multi'empty :: a Source #

multi'mconcat :: [a] -> a Source #

MultiMonoid Last (Maybe a) Source # 
MultiMonoid First (Maybe a) Source # 
Ord a => MultiMonoid MaxMaybe (Maybe a) Source # 
Ord a => MultiMonoid MinMaybe (Maybe a) Source # 
MultiMonoid Addition [a] Source # 

Methods

multi'empty :: [a] Source #

multi'mconcat :: [[a]] -> [a] Source #

MultiMonoid ArrowComposition (a -> a) Source # 

Methods

multi'empty :: a -> a Source #

multi'mconcat :: [a -> a] -> a -> a Source #

Monad m => MultiMonoid ArrowComposition (Kleisli m a a) Source # 

Methods

multi'empty :: Kleisli m a a Source #

multi'mconcat :: [Kleisli m a a] -> Kleisli m a a Source #

MultiMonoid x a => MultiMonoid (MultiDual x) a Source # 

Methods

multi'empty :: a Source #

multi'mconcat :: [a] -> a Source #

Default

data Default Source #

Instances

Conjunction and disjunction

data Disjunction Source #

Instances

MultiMonoid Addition Int Source # 
MultiMonoid Addition Integer Source # 
MultiMonoid Addition Natural Source # 
MultiMonoid Or Bool Source # 
MultiSemigroup Addition Int Source # 
MultiSemigroup Addition Integer Source # 
MultiSemigroup Addition Natural Source # 
MultiSemigroup Or Bool Source # 
MultiMonoid Addition [a] Source # 

Methods

multi'empty :: [a] Source #

multi'mconcat :: [[a]] -> [a] Source #

MultiSemigroup Addition [a] Source # 

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 # 

Addition and multiplication

multi'sum :: (Foldable t, MultiMonoid Addition a) => t a -> a Source #

The sum of the numbers in a structure.

Equivalent to multi'fold @Addition.

Akin to sum.

multi'product :: (Foldable t, MultiMonoid Multiplication a) => t a -> a Source #

The product of the numbers of a structure.

Equivalent to multi'fold @Multiplication.

Akin to product.

Boolean and and or

multi'and :: (Foldable t, MultiMonoid And a) => t a -> a Source #

The conjunction of a container of Bools.

Equivalent to multi'fold @And.

Akin to and.

multi'or :: (Foldable t, MultiMonoid Or a) => t a -> a Source #

The disjunction of a container of Bools.

Equivalent to multi'fold @Or.

Akin to or.

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

data Min Source #

Instances

Ord a => MultiSemigroup Min a Source # 

Methods

multi'append :: a -> a -> a Source #

multi'sconcat :: NonEmpty a -> a Source #

multi'stimes :: Integral b => b -> a -> a Source #

data Max Source #

Instances

Ord a => MultiSemigroup Max a Source # 

Methods

multi'append :: a -> a -> a Source #

multi'sconcat :: NonEmpty a -> a Source #

multi'stimes :: Integral b => b -> a -> a Source #

First and last

Arrow composition

data ArrowComposition Source #

Instances

MultiMonoid ArrowComposition (a -> a) Source # 

Methods

multi'empty :: a -> a Source #

multi'mconcat :: [a -> a] -> a -> a Source #

MultiSemigroup ArrowComposition (a -> a) Source # 

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 # 

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 # 

Methods

multi'append :: Kleisli m a a -> Kleisli m a a -> Kleisli m a a Source #

multi'sconcat :: NonEmpty (Kleisli m a a) -> Kleisli m a a Source #

multi'stimes :: Integral b => b -> Kleisli m a a -> Kleisli m a a Source #

Dual

data MultiDual a Source #

Instances

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.

Looking for elements

multi'find :: Foldable t => (a -> Bool) -> t a -> Maybe a Source #

Takes a predicate and a structure and returns the leftmost element of the structure matching the predicate, or Nothing if there is no such element.

Akin to find.