difference-monoid-0.1.0.0

Copyright(c) Donnacha Oisín Kidney 2018
LicenseMIT
Maintainer[email protected]
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Data.Monoid.Diff

Contents

Description

This module provides the Difference Monoid, which adds subtraction to arbitrary monoids.

This has a number of uses:

  • Diff (Product a) will give you a type similar to Ratio. Here, the "subtraction" operation is division. For example:

    >>> (1 :-: 2) <> (3 :-: 4) :: Diff (Product Int)
    Product {getProduct = 3} :-: Product {getProduct = 8}
    
  • In a similar vein, Diff (Sum a) will add subtraction to a numeric type:

    >>> runDiff (-) (diff 2 <> diff 3 <> invert (diff 4)) :: Sum Natural
    Sum {getSum = 1}
    

    This will let you work with nonnegative types, where you need some form of subtraction (for, e.g., differences, hence the name), and you only want to check for underflow once.

  • Using the above example, in particular, we get a monoid for averages:

    >>> import Data.Function (on)
    >>> let avg = runDiff ((%) `on` getProduct.getSum) . foldMap (fmap Sum . diff . Product)
    >>> avg [1,4,3,2,5]
    3 % 1
    

The Monoid and Semigroup laws hold in a pretty straightforward way, provided the underlying type also follows those laws.

For the Group laws, the underlying type must be a cancellative semigroup.

A cancellative semigroup is one where

  • a <> b = a <> c implies b = c
  • b <> a = c <> a implies b = c

If this does not hold, than the equivalence only holds modulo the the addition of some constant

Most common semigroups are cancellative, however notable exceptions include the cross product of vectors, matrix multiplication, and sets:

fromList [1] <> fromList [1,2] = fromList [1] <> fromList [2]

This type is known formally as the Grothendieck group.

Synopsis

The Diff Type

data Diff a Source #

The Difference Monoid.

Constructors

!a :-: !a infixl 6 

Instances

Monad Diff Source # 

Methods

(>>=) :: Diff a -> (a -> Diff b) -> Diff b #

(>>) :: Diff a -> Diff b -> Diff b #

return :: a -> Diff a #

fail :: String -> Diff a #

Functor Diff Source # 

Methods

fmap :: (a -> b) -> Diff a -> Diff b #

(<$) :: a -> Diff b -> Diff a #

MonadFix Diff Source # 

Methods

mfix :: (a -> Diff a) -> Diff a #

Applicative Diff Source # 

Methods

pure :: a -> Diff a #

(<*>) :: Diff (a -> b) -> Diff a -> Diff b #

liftA2 :: (a -> b -> c) -> Diff a -> Diff b -> Diff c #

(*>) :: Diff a -> Diff b -> Diff b #

(<*) :: Diff a -> Diff b -> Diff a #

Foldable Diff Source # 

Methods

fold :: Monoid m => Diff m -> m #

foldMap :: Monoid m => (a -> m) -> Diff a -> m #

foldr :: (a -> b -> b) -> b -> Diff a -> b #

foldr' :: (a -> b -> b) -> b -> Diff a -> b #

foldl :: (b -> a -> b) -> b -> Diff a -> b #

foldl' :: (b -> a -> b) -> b -> Diff a -> b #

foldr1 :: (a -> a -> a) -> Diff a -> a #

foldl1 :: (a -> a -> a) -> Diff a -> a #

toList :: Diff a -> [a] #

null :: Diff a -> Bool #

length :: Diff a -> Int #

elem :: Eq a => a -> Diff a -> Bool #

maximum :: Ord a => Diff a -> a #

minimum :: Ord a => Diff a -> a #

sum :: Num a => Diff a -> a #

product :: Num a => Diff a -> a #

Traversable Diff Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Diff a -> f (Diff b) #

sequenceA :: Applicative f => Diff (f a) -> f (Diff a) #

mapM :: Monad m => (a -> m b) -> Diff a -> m (Diff b) #

sequence :: Monad m => Diff (m a) -> m (Diff a) #

Distributive Diff Source # 

Methods

distribute :: Functor f => f (Diff a) -> Diff (f a) #

collect :: Functor f => (a -> Diff b) -> f a -> Diff (f b) #

distributeM :: Monad m => m (Diff a) -> Diff (m a) #

collectM :: Monad m => (a -> Diff b) -> m a -> Diff (m b) #

Representable Diff Source # 

Associated Types

type Rep (Diff :: * -> *) :: * #

Methods

tabulate :: (Rep Diff -> a) -> Diff a #

index :: Diff a -> Rep Diff -> a #

Read1 Diff Source # 

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Diff a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Diff a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Diff a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Diff a] #

Show1 Diff Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Diff a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Diff a] -> ShowS #

MonadZip Diff Source # 

Methods

mzip :: Diff a -> Diff b -> Diff (a, b) #

mzipWith :: (a -> b -> c) -> Diff a -> Diff b -> Diff c #

munzip :: Diff (a, b) -> (Diff a, Diff b) #

Comonad Diff Source # 

Methods

extract :: Diff a -> a #

duplicate :: Diff a -> Diff (Diff a) #

extend :: (Diff a -> b) -> Diff a -> Diff b #

ComonadApply Diff Source # 

Methods

(<@>) :: Diff (a -> b) -> Diff a -> Diff b #

(@>) :: Diff a -> Diff b -> Diff b #

(<@) :: Diff a -> Diff b -> Diff a #

Traversable1 Diff Source # 

Methods

traverse1 :: Apply f => (a -> f b) -> Diff a -> f (Diff b) #

sequence1 :: Apply f => Diff (f b) -> f (Diff b) #

Foldable1 Diff Source # 

Methods

fold1 :: Semigroup m => Diff m -> m #

foldMap1 :: Semigroup m => (a -> m) -> Diff a -> m #

toNonEmpty :: Diff a -> NonEmpty a #

Apply Diff Source # 

Methods

(<.>) :: Diff (a -> b) -> Diff a -> Diff b #

(.>) :: Diff a -> Diff b -> Diff b #

(<.) :: Diff a -> Diff b -> Diff a #

liftF2 :: (a -> b -> c) -> Diff a -> Diff b -> Diff c #

Bind Diff Source # 

Methods

(>>-) :: Diff a -> (a -> Diff b) -> Diff b #

join :: Diff (Diff a) -> Diff a #

Extend Diff Source # 

Methods

duplicated :: Diff a -> Diff (Diff a) #

extended :: (Diff a -> b) -> Diff a -> Diff b #

Adjunction Parity Diff Source # 

Methods

unit :: a -> Diff (Parity a) #

counit :: Parity (Diff a) -> a #

leftAdjunct :: (Parity a -> b) -> a -> Diff b #

rightAdjunct :: (a -> Diff b) -> Parity a -> b #

Bounded a => Bounded (Diff a) Source # 

Methods

minBound :: Diff a #

maxBound :: Diff a #

(Eq a, Semigroup a) => Eq (Diff a) Source # 

Methods

(==) :: Diff a -> Diff a -> Bool #

(/=) :: Diff a -> Diff a -> Bool #

Data a => Data (Diff a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Diff a -> c (Diff a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Diff a) #

toConstr :: Diff a -> Constr #

dataTypeOf :: Diff a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Diff a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Diff a)) #

gmapT :: (forall b. Data b => b -> b) -> Diff a -> Diff a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Diff a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Diff a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Diff a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Diff a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Diff a -> m (Diff a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Diff a -> m (Diff a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Diff a -> m (Diff a) #

(Ord a, Semigroup a) => Ord (Diff a) Source # 

Methods

compare :: Diff a -> Diff a -> Ordering #

(<) :: Diff a -> Diff a -> Bool #

(<=) :: Diff a -> Diff a -> Bool #

(>) :: Diff a -> Diff a -> Bool #

(>=) :: Diff a -> Diff a -> Bool #

max :: Diff a -> Diff a -> Diff a #

min :: Diff a -> Diff a -> Diff a #

Read a => Read (Diff a) Source # 
Show a => Show (Diff a) Source # 

Methods

showsPrec :: Int -> Diff a -> ShowS #

show :: Diff a -> String #

showList :: [Diff a] -> ShowS #

Generic (Diff a) Source # 

Associated Types

type Rep (Diff a) :: * -> * #

Methods

from :: Diff a -> Rep (Diff a) x #

to :: Rep (Diff a) x -> Diff a #

Semigroup a => Semigroup (Diff a) Source # 

Methods

(<>) :: Diff a -> Diff a -> Diff a #

sconcat :: NonEmpty (Diff a) -> Diff a #

stimes :: Integral b => b -> Diff a -> Diff a #

Monoid a => Monoid (Diff a) Source # 

Methods

mempty :: Diff a #

mappend :: Diff a -> Diff a -> Diff a #

mconcat :: [Diff a] -> Diff a #

NFData a => NFData (Diff a) Source # 

Methods

rnf :: Diff a -> () #

Monoid a => Group (Diff a) Source # 

Methods

invert :: Diff a -> Diff a #

pow :: Integral x => Diff a -> x -> Diff a #

Generic1 * Diff Source # 

Associated Types

type Rep1 Diff (f :: Diff -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 Diff f a #

to1 :: Rep1 Diff f a -> f a #

type Rep Diff Source # 
type Rep Diff = Bool
type Rep (Diff a) Source # 
type Rep (Diff a) = D1 * (MetaData "Diff" "Data.Monoid.Diff.Internal" "difference-monoid-0.1.0.0-6GZ7n3SsUmUHrUzugzcGeo" False) (C1 * (MetaCons ":-:" (InfixI LeftAssociative 6) False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * a))))
type Rep1 * Diff Source # 
type Rep1 * Diff = D1 * (MetaData "Diff" "Data.Monoid.Diff.Internal" "difference-monoid-0.1.0.0-6GZ7n3SsUmUHrUzugzcGeo" False) (C1 * (MetaCons ":-:" (InfixI LeftAssociative 6) False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1)))

Functions for working with Diff

diff :: Monoid a => a -> Diff a Source #

Lift a monoid into the difference monoid.

>>> diff (Sum 1)
Sum {getSum = 1} :-: Sum {getSum = 0}

retract :: Group a => Diff a -> a Source #

The inverse of diff.

retract . diff = id

foldDiff :: Group b => (a -> b) -> Diff a -> b Source #

A group homomorphism given a monoid homomorphism.

runDiff :: (a -> a -> b) -> Diff a -> b Source #

Interpret the difference using a subtraction function.

normalize :: (a -> a -> (a, a)) -> Diff a -> Diff a Source #

Given a "normalizing" function, try simplify the representation.

For instance, one such normalizing function may be to take the numeric difference of two types:

>>> let sumNorm x y = if x >= y then (x - y, 0) else (0, y - x)
>>> normalize sumNorm ((foldMap (diff.Sum) [1..10]) <> (invert (foldMap (diff.Sum) [1..5])))
Sum {getSum = 40} :-: Sum {getSum = 0}

Re-Exports from Group

class Monoid m => Group m where #

A Group is a Monoid plus a function, invert, such that:

a <> invert a == mempty
invert a <> a == mempty

Minimal complete definition

invert

Methods

invert :: m -> m #

pow :: Integral x => m -> x -> m #

pow a n == a <> a <> ... <> a
 (n lots of a)

If n is negative, the result is inverted.

Instances

Group () 

Methods

invert :: () -> () #

pow :: Integral x => () -> x -> () #

Group Odd # 

Methods

invert :: Odd -> Odd #

pow :: Integral x => Odd -> x -> Odd #

Group a => Group (Dual a) 

Methods

invert :: Dual a -> Dual a #

pow :: Integral x => Dual a -> x -> Dual a #

Num a => Group (Sum a) 

Methods

invert :: Sum a -> Sum a #

pow :: Integral x => Sum a -> x -> Sum a #

Fractional a => Group (Product a) 

Methods

invert :: Product a -> Product a #

pow :: Integral x => Product a -> x -> Product a #

Monoid a => Group (Diff a) # 

Methods

invert :: Diff a -> Diff a #

pow :: Integral x => Diff a -> x -> Diff a #

Group b => Group (a -> b) 

Methods

invert :: (a -> b) -> a -> b #

pow :: Integral x => (a -> b) -> x -> a -> b #

(Group a, Group b) => Group (a, b) 

Methods

invert :: (a, b) -> (a, b) #

pow :: Integral x => (a, b) -> x -> (a, b) #

(Group a, Group b, Group c) => Group (a, b, c) 

Methods

invert :: (a, b, c) -> (a, b, c) #

pow :: Integral x => (a, b, c) -> x -> (a, b, c) #

(Group a, Group b, Group c, Group d) => Group (a, b, c, d) 

Methods

invert :: (a, b, c, d) -> (a, b, c, d) #

pow :: Integral x => (a, b, c, d) -> x -> (a, b, c, d) #

(Group a, Group b, Group c, Group d, Group e) => Group (a, b, c, d, e) 

Methods

invert :: (a, b, c, d, e) -> (a, b, c, d, e) #

pow :: Integral x => (a, b, c, d, e) -> x -> (a, b, c, d, e) #