monoid-subclasses-0.4.6.1: Subclasses of Monoid

Safe HaskellTrustworthy
LanguageHaskell2010

Data.Monoid.Cancellative

Contents

Description

This module defines the Monoid => ReductiveMonoid => (CancellativeMonoid, GCDMonoid) class hierarchy.

The ReductiveMonoid class introduces operation </> which is the inverse of <>. For the Sum monoid, this operation is subtraction; for Product it is division and for Set it's the set difference. A ReductiveMonoid is not a full group because </> may return Nothing.

The CancellativeMonoid subclass does not add any operation but it provides the additional guarantee that <> can always be undone with </>. Thus Sum is a CancellativeMonoid but Product is not because (0*n)/0 is not defined.

The GCDMonoid subclass adds the gcd operation which takes two monoidal arguments and finds their greatest common divisor, or (more generally) the greatest monoid that can be extracted with the </> operation from both.

All monoid subclasses listed above are for Abelian, i.e., commutative or symmetric monoids. Since most practical monoids in Haskell are not Abelian, each of the these classes has two symmetric superclasses:

Synopsis

Symmetric, commutative monoid classes

class Monoid m => CommutativeMonoid m Source #

Class of all Abelian ({i.e.}, commutative) monoids that satisfy the commutativity property:

a <> b == b <> a
Instances
CommutativeMonoid () Source # 
Instance details

Defined in Data.Monoid.Cancellative

CommutativeMonoid IntSet Source # 
Instance details

Defined in Data.Monoid.Cancellative

CommutativeMonoid a => CommutativeMonoid (Dual a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Num a => CommutativeMonoid (Sum a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Num a => CommutativeMonoid (Product a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Ord a => CommutativeMonoid (Set a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

(CommutativeMonoid a, CommutativeMonoid b) => CommutativeMonoid (a, b) Source # 
Instance details

Defined in Data.Monoid.Cancellative

(CommutativeMonoid a, CommutativeMonoid b, CommutativeMonoid c) => CommutativeMonoid (a, b, c) Source # 
Instance details

Defined in Data.Monoid.Cancellative

(CommutativeMonoid a, CommutativeMonoid b, CommutativeMonoid c, CommutativeMonoid d) => CommutativeMonoid (a, b, c, d) Source # 
Instance details

Defined in Data.Monoid.Cancellative

class (CommutativeMonoid m, LeftReductiveMonoid m, RightReductiveMonoid m) => ReductiveMonoid m where Source #

Class of Abelian monoids with a partial inverse for the Monoid <> operation. The inverse operation </> must satisfy the following laws:

maybe a (b <>) (a </> b) == a
maybe a (<> b) (a </> b) == a

Minimal complete definition

(</>)

Methods

(</>) :: m -> m -> Maybe m infix 5 Source #

Instances
ReductiveMonoid () Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

(</>) :: () -> () -> Maybe () Source #

ReductiveMonoid IntSet Source # 
Instance details

Defined in Data.Monoid.Cancellative

ReductiveMonoid a => ReductiveMonoid (Dual a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

(</>) :: Dual a -> Dual a -> Maybe (Dual a) Source #

Integral a => ReductiveMonoid (Sum a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

(</>) :: Sum a -> Sum a -> Maybe (Sum a) Source #

Integral a => ReductiveMonoid (Product a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

(</>) :: Product a -> Product a -> Maybe (Product a) Source #

Ord a => ReductiveMonoid (Set a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

(</>) :: Set a -> Set a -> Maybe (Set a) Source #

(ReductiveMonoid a, ReductiveMonoid b) => ReductiveMonoid (a, b) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

(</>) :: (a, b) -> (a, b) -> Maybe (a, b) Source #

(ReductiveMonoid a, ReductiveMonoid b, ReductiveMonoid c) => ReductiveMonoid (a, b, c) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

(</>) :: (a, b, c) -> (a, b, c) -> Maybe (a, b, c) Source #

(ReductiveMonoid a, ReductiveMonoid b, ReductiveMonoid c, ReductiveMonoid d) => ReductiveMonoid (a, b, c, d) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

(</>) :: (a, b, c, d) -> (a, b, c, d) -> Maybe (a, b, c, d) Source #

class (LeftCancellativeMonoid m, RightCancellativeMonoid m, ReductiveMonoid m) => CancellativeMonoid m Source #

Subclass of ReductiveMonoid where </> is a complete inverse of the Monoid <> operation. The class instances must satisfy the following additional laws:

(a <> b) </> a == Just b
(a <> b) </> b == Just a

class (ReductiveMonoid m, LeftGCDMonoid m, RightGCDMonoid m) => GCDMonoid m where Source #

Class of Abelian monoids that allow the greatest common denominator to be found for any two given values. The operations must satisfy the following laws:

gcd a b == commonPrefix a b == commonSuffix a b
Just a' = a </> p && Just b' = b </> p
   where p = gcd a b

If a GCDMonoid happens to also be a CancellativeMonoid, it should additionally satisfy the following laws:

gcd (a <> b) (a <> c) == a <> gcd b c
gcd (a <> c) (b <> c) == gcd a b <> c

Minimal complete definition

gcd

Methods

gcd :: m -> m -> m Source #

Instances
GCDMonoid () Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

gcd :: () -> () -> () Source #

GCDMonoid IntSet Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

gcd :: IntSet -> IntSet -> IntSet Source #

GCDMonoid a => GCDMonoid (Dual a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

gcd :: Dual a -> Dual a -> Dual a Source #

(Integral a, Ord a) => GCDMonoid (Sum a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

gcd :: Sum a -> Sum a -> Sum a Source #

Integral a => GCDMonoid (Product a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

gcd :: Product a -> Product a -> Product a Source #

Ord a => GCDMonoid (Set a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

gcd :: Set a -> Set a -> Set a Source #

(GCDMonoid a, GCDMonoid b) => GCDMonoid (a, b) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

gcd :: (a, b) -> (a, b) -> (a, b) Source #

(GCDMonoid a, GCDMonoid b, GCDMonoid c) => GCDMonoid (a, b, c) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

gcd :: (a, b, c) -> (a, b, c) -> (a, b, c) Source #

(GCDMonoid a, GCDMonoid b, GCDMonoid c, GCDMonoid d) => GCDMonoid (a, b, c, d) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

gcd :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) Source #

Asymmetric monoid classes

class Monoid m => LeftReductiveMonoid m where Source #

Class of monoids with a left inverse of mappend, satisfying the following law:

isPrefixOf a b == isJust (stripPrefix a b)
maybe b (a <>) (stripPrefix a b) == b
a `isPrefixOf` (a <> b)

| Every instance definition has to implement at least the stripPrefix method. Its complexity should be no worse than linear in the length of the prefix argument.

Minimal complete definition

stripPrefix

Methods

isPrefixOf :: m -> m -> Bool Source #

stripPrefix :: m -> m -> Maybe m Source #

Instances
LeftReductiveMonoid () Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

isPrefixOf :: () -> () -> Bool Source #

stripPrefix :: () -> () -> Maybe () Source #

LeftReductiveMonoid ByteString Source # 
Instance details

Defined in Data.Monoid.Cancellative

LeftReductiveMonoid ByteString Source # 
Instance details

Defined in Data.Monoid.Cancellative

LeftReductiveMonoid IntSet Source # 
Instance details

Defined in Data.Monoid.Cancellative

LeftReductiveMonoid Text Source # 
Instance details

Defined in Data.Monoid.Cancellative

LeftReductiveMonoid Text Source # 
Instance details

Defined in Data.Monoid.Cancellative

LeftReductiveMonoid ByteStringUTF8 Source # 
Instance details

Defined in Data.Monoid.Instances.ByteString.UTF8

Eq x => LeftReductiveMonoid [x] Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

isPrefixOf :: [x] -> [x] -> Bool Source #

stripPrefix :: [x] -> [x] -> Maybe [x] Source #

LeftReductiveMonoid x => LeftReductiveMonoid (Maybe x) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

isPrefixOf :: Maybe x -> Maybe x -> Bool Source #

stripPrefix :: Maybe x -> Maybe x -> Maybe (Maybe x) Source #

RightReductiveMonoid a => LeftReductiveMonoid (Dual a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

isPrefixOf :: Dual a -> Dual a -> Bool Source #

stripPrefix :: Dual a -> Dual a -> Maybe (Dual a) Source #

Integral a => LeftReductiveMonoid (Sum a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

isPrefixOf :: Sum a -> Sum a -> Bool Source #

stripPrefix :: Sum a -> Sum a -> Maybe (Sum a) Source #

Integral a => LeftReductiveMonoid (Product a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

LeftReductiveMonoid (IntMap a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Eq a => LeftReductiveMonoid (Seq a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

isPrefixOf :: Seq a -> Seq a -> Bool Source #

stripPrefix :: Seq a -> Seq a -> Maybe (Seq a) Source #

Ord a => LeftReductiveMonoid (Set a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

isPrefixOf :: Set a -> Set a -> Bool Source #

stripPrefix :: Set a -> Set a -> Maybe (Set a) Source #

Eq a => LeftReductiveMonoid (Vector a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

(StableFactorialMonoid m, TextualMonoid m, LeftReductiveMonoid m) => LeftReductiveMonoid (LinePositioned m) Source # 
Instance details

Defined in Data.Monoid.Instances.Positioned

(StableFactorialMonoid m, LeftReductiveMonoid m) => LeftReductiveMonoid (OffsetPositioned m) Source # 
Instance details

Defined in Data.Monoid.Instances.Positioned

(LeftReductiveMonoid a, StableFactorialMonoid a) => LeftReductiveMonoid (Measured a) Source # 
Instance details

Defined in Data.Monoid.Instances.Measured

(LeftReductiveMonoid a, StableFactorialMonoid a) => LeftReductiveMonoid (Concat a) Source # 
Instance details

Defined in Data.Monoid.Instances.Concat

(LeftReductiveMonoid a, LeftReductiveMonoid b) => LeftReductiveMonoid (a, b) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

isPrefixOf :: (a, b) -> (a, b) -> Bool Source #

stripPrefix :: (a, b) -> (a, b) -> Maybe (a, b) Source #

Ord k => LeftReductiveMonoid (Map k a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

isPrefixOf :: Map k a -> Map k a -> Bool Source #

stripPrefix :: Map k a -> Map k a -> Maybe (Map k a) Source #

(LeftReductiveMonoid a, LeftReductiveMonoid b) => LeftReductiveMonoid (Stateful a b) Source # 
Instance details

Defined in Data.Monoid.Instances.Stateful

Methods

isPrefixOf :: Stateful a b -> Stateful a b -> Bool Source #

stripPrefix :: Stateful a b -> Stateful a b -> Maybe (Stateful a b) Source #

(LeftReductiveMonoid a, LeftReductiveMonoid b, LeftReductiveMonoid c) => LeftReductiveMonoid (a, b, c) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

isPrefixOf :: (a, b, c) -> (a, b, c) -> Bool Source #

stripPrefix :: (a, b, c) -> (a, b, c) -> Maybe (a, b, c) Source #

(LeftReductiveMonoid a, LeftReductiveMonoid b, LeftReductiveMonoid c, LeftReductiveMonoid d) => LeftReductiveMonoid (a, b, c, d) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

isPrefixOf :: (a, b, c, d) -> (a, b, c, d) -> Bool Source #

stripPrefix :: (a, b, c, d) -> (a, b, c, d) -> Maybe (a, b, c, d) Source #

class Monoid m => RightReductiveMonoid m where Source #

Class of monoids with a right inverse of mappend, satisfying the following law:

isSuffixOf a b == isJust (stripSuffix a b)
maybe b (<> a) (stripSuffix a b) == b
b `isSuffixOf` (a <> b)

| Every instance definition has to implement at least the stripSuffix method. Its complexity should be no worse than linear in the length of the suffix argument.

Minimal complete definition

stripSuffix

Methods

isSuffixOf :: m -> m -> Bool Source #

stripSuffix :: m -> m -> Maybe m Source #

Instances
RightReductiveMonoid () Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

isSuffixOf :: () -> () -> Bool Source #

stripSuffix :: () -> () -> Maybe () Source #

RightReductiveMonoid ByteString Source # 
Instance details

Defined in Data.Monoid.Cancellative

RightReductiveMonoid ByteString Source # 
Instance details

Defined in Data.Monoid.Cancellative

RightReductiveMonoid IntSet Source # 
Instance details

Defined in Data.Monoid.Cancellative

RightReductiveMonoid Text Source # 
Instance details

Defined in Data.Monoid.Cancellative

RightReductiveMonoid Text Source # 
Instance details

Defined in Data.Monoid.Cancellative

RightReductiveMonoid x => RightReductiveMonoid (Maybe x) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

isSuffixOf :: Maybe x -> Maybe x -> Bool Source #

stripSuffix :: Maybe x -> Maybe x -> Maybe (Maybe x) Source #

LeftReductiveMonoid a => RightReductiveMonoid (Dual a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

isSuffixOf :: Dual a -> Dual a -> Bool Source #

stripSuffix :: Dual a -> Dual a -> Maybe (Dual a) Source #

Integral a => RightReductiveMonoid (Sum a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

isSuffixOf :: Sum a -> Sum a -> Bool Source #

stripSuffix :: Sum a -> Sum a -> Maybe (Sum a) Source #

Integral a => RightReductiveMonoid (Product a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Eq a => RightReductiveMonoid (Seq a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

isSuffixOf :: Seq a -> Seq a -> Bool Source #

stripSuffix :: Seq a -> Seq a -> Maybe (Seq a) Source #

Ord a => RightReductiveMonoid (Set a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

isSuffixOf :: Set a -> Set a -> Bool Source #

stripSuffix :: Set a -> Set a -> Maybe (Set a) Source #

Eq a => RightReductiveMonoid (Vector a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

(StableFactorialMonoid m, TextualMonoid m, RightReductiveMonoid m) => RightReductiveMonoid (LinePositioned m) Source # 
Instance details

Defined in Data.Monoid.Instances.Positioned

(StableFactorialMonoid m, RightReductiveMonoid m) => RightReductiveMonoid (OffsetPositioned m) Source # 
Instance details

Defined in Data.Monoid.Instances.Positioned

(RightReductiveMonoid a, StableFactorialMonoid a) => RightReductiveMonoid (Measured a) Source # 
Instance details

Defined in Data.Monoid.Instances.Measured

(RightReductiveMonoid a, StableFactorialMonoid a) => RightReductiveMonoid (Concat a) Source # 
Instance details

Defined in Data.Monoid.Instances.Concat

(RightReductiveMonoid a, RightReductiveMonoid b) => RightReductiveMonoid (a, b) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

isSuffixOf :: (a, b) -> (a, b) -> Bool Source #

stripSuffix :: (a, b) -> (a, b) -> Maybe (a, b) Source #

(RightReductiveMonoid a, RightReductiveMonoid b) => RightReductiveMonoid (Stateful a b) Source # 
Instance details

Defined in Data.Monoid.Instances.Stateful

Methods

isSuffixOf :: Stateful a b -> Stateful a b -> Bool Source #

stripSuffix :: Stateful a b -> Stateful a b -> Maybe (Stateful a b) Source #

(RightReductiveMonoid a, RightReductiveMonoid b, RightReductiveMonoid c) => RightReductiveMonoid (a, b, c) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

isSuffixOf :: (a, b, c) -> (a, b, c) -> Bool Source #

stripSuffix :: (a, b, c) -> (a, b, c) -> Maybe (a, b, c) Source #

(RightReductiveMonoid a, RightReductiveMonoid b, RightReductiveMonoid c, RightReductiveMonoid d) => RightReductiveMonoid (a, b, c, d) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

isSuffixOf :: (a, b, c, d) -> (a, b, c, d) -> Bool Source #

stripSuffix :: (a, b, c, d) -> (a, b, c, d) -> Maybe (a, b, c, d) Source #

class LeftReductiveMonoid m => LeftCancellativeMonoid m Source #

Subclass of LeftReductiveMonoid where stripPrefix is a complete inverse of <>, satisfying the following additional law:

stripPrefix a (a <> b) == Just b
Instances
LeftCancellativeMonoid () Source # 
Instance details

Defined in Data.Monoid.Cancellative

LeftCancellativeMonoid ByteString Source # 
Instance details

Defined in Data.Monoid.Cancellative

LeftCancellativeMonoid ByteString Source # 
Instance details

Defined in Data.Monoid.Cancellative

LeftCancellativeMonoid Text Source # 
Instance details

Defined in Data.Monoid.Cancellative

LeftCancellativeMonoid Text Source # 
Instance details

Defined in Data.Monoid.Cancellative

LeftCancellativeMonoid ByteStringUTF8 Source # 
Instance details

Defined in Data.Monoid.Instances.ByteString.UTF8

Eq x => LeftCancellativeMonoid [x] Source # 
Instance details

Defined in Data.Monoid.Cancellative

RightCancellativeMonoid a => LeftCancellativeMonoid (Dual a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Integral a => LeftCancellativeMonoid (Sum a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Eq a => LeftCancellativeMonoid (Seq a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Eq a => LeftCancellativeMonoid (Vector a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

(LeftCancellativeMonoid a, LeftCancellativeMonoid b) => LeftCancellativeMonoid (a, b) Source # 
Instance details

Defined in Data.Monoid.Cancellative

(LeftCancellativeMonoid a, LeftCancellativeMonoid b, LeftCancellativeMonoid c) => LeftCancellativeMonoid (a, b, c) Source # 
Instance details

Defined in Data.Monoid.Cancellative

(LeftCancellativeMonoid a, LeftCancellativeMonoid b, LeftCancellativeMonoid c, LeftCancellativeMonoid d) => LeftCancellativeMonoid (a, b, c, d) Source # 
Instance details

Defined in Data.Monoid.Cancellative

class RightReductiveMonoid m => RightCancellativeMonoid m Source #

Subclass of LeftReductiveMonoid where stripPrefix is a complete inverse of <>, satisfying the following additional law:

stripSuffix b (a <> b) == Just a

class LeftReductiveMonoid m => LeftGCDMonoid m where Source #

Class of monoids capable of finding the equivalent of greatest common divisor on the left side of two monoidal values. The methods' complexity should be no worse than linear in the length of the common prefix. The following laws must be respected:

stripCommonPrefix a b == (p, a', b')
   where p = commonPrefix a b
         Just a' = stripPrefix p a
         Just b' = stripPrefix p b
p == commonPrefix a b && p <> a' == a && p <> b' == b
   where (p, a', b') = stripCommonPrefix a b

Minimal complete definition

commonPrefix | stripCommonPrefix

Methods

commonPrefix :: m -> m -> m Source #

stripCommonPrefix :: m -> m -> (m, m, m) Source #

Instances
LeftGCDMonoid () Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

commonPrefix :: () -> () -> () Source #

stripCommonPrefix :: () -> () -> ((), (), ()) Source #

LeftGCDMonoid ByteString Source # 
Instance details

Defined in Data.Monoid.Cancellative

LeftGCDMonoid ByteString Source # 
Instance details

Defined in Data.Monoid.Cancellative

LeftGCDMonoid IntSet Source # 
Instance details

Defined in Data.Monoid.Cancellative

LeftGCDMonoid Text Source # 
Instance details

Defined in Data.Monoid.Cancellative

LeftGCDMonoid Text Source # 
Instance details

Defined in Data.Monoid.Cancellative

LeftGCDMonoid ByteStringUTF8 Source # 
Instance details

Defined in Data.Monoid.Instances.ByteString.UTF8

Eq x => LeftGCDMonoid [x] Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

commonPrefix :: [x] -> [x] -> [x] Source #

stripCommonPrefix :: [x] -> [x] -> ([x], [x], [x]) Source #

LeftGCDMonoid x => LeftGCDMonoid (Maybe x) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

commonPrefix :: Maybe x -> Maybe x -> Maybe x Source #

stripCommonPrefix :: Maybe x -> Maybe x -> (Maybe x, Maybe x, Maybe x) Source #

RightGCDMonoid a => LeftGCDMonoid (Dual a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

commonPrefix :: Dual a -> Dual a -> Dual a Source #

stripCommonPrefix :: Dual a -> Dual a -> (Dual a, Dual a, Dual a) Source #

(Integral a, Ord a) => LeftGCDMonoid (Sum a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

commonPrefix :: Sum a -> Sum a -> Sum a Source #

stripCommonPrefix :: Sum a -> Sum a -> (Sum a, Sum a, Sum a) Source #

Integral a => LeftGCDMonoid (Product a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Eq a => LeftGCDMonoid (IntMap a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Eq a => LeftGCDMonoid (Seq a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

commonPrefix :: Seq a -> Seq a -> Seq a Source #

stripCommonPrefix :: Seq a -> Seq a -> (Seq a, Seq a, Seq a) Source #

Ord a => LeftGCDMonoid (Set a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

commonPrefix :: Set a -> Set a -> Set a Source #

stripCommonPrefix :: Set a -> Set a -> (Set a, Set a, Set a) Source #

Eq a => LeftGCDMonoid (Vector a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

(StableFactorialMonoid m, TextualMonoid m, LeftGCDMonoid m) => LeftGCDMonoid (LinePositioned m) Source # 
Instance details

Defined in Data.Monoid.Instances.Positioned

(StableFactorialMonoid m, LeftGCDMonoid m) => LeftGCDMonoid (OffsetPositioned m) Source # 
Instance details

Defined in Data.Monoid.Instances.Positioned

(LeftGCDMonoid a, StableFactorialMonoid a) => LeftGCDMonoid (Measured a) Source # 
Instance details

Defined in Data.Monoid.Instances.Measured

(LeftGCDMonoid a, StableFactorialMonoid a) => LeftGCDMonoid (Concat a) Source # 
Instance details

Defined in Data.Monoid.Instances.Concat

(LeftGCDMonoid a, LeftGCDMonoid b) => LeftGCDMonoid (a, b) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

commonPrefix :: (a, b) -> (a, b) -> (a, b) Source #

stripCommonPrefix :: (a, b) -> (a, b) -> ((a, b), (a, b), (a, b)) Source #

(Ord k, Eq a) => LeftGCDMonoid (Map k a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

commonPrefix :: Map k a -> Map k a -> Map k a Source #

stripCommonPrefix :: Map k a -> Map k a -> (Map k a, Map k a, Map k a) Source #

(LeftGCDMonoid a, LeftGCDMonoid b) => LeftGCDMonoid (Stateful a b) Source # 
Instance details

Defined in Data.Monoid.Instances.Stateful

Methods

commonPrefix :: Stateful a b -> Stateful a b -> Stateful a b Source #

stripCommonPrefix :: Stateful a b -> Stateful a b -> (Stateful a b, Stateful a b, Stateful a b) Source #

(LeftGCDMonoid a, LeftGCDMonoid b, LeftGCDMonoid c) => LeftGCDMonoid (a, b, c) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

commonPrefix :: (a, b, c) -> (a, b, c) -> (a, b, c) Source #

stripCommonPrefix :: (a, b, c) -> (a, b, c) -> ((a, b, c), (a, b, c), (a, b, c)) Source #

(LeftGCDMonoid a, LeftGCDMonoid b, LeftGCDMonoid c, LeftGCDMonoid d) => LeftGCDMonoid (a, b, c, d) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

commonPrefix :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) Source #

stripCommonPrefix :: (a, b, c, d) -> (a, b, c, d) -> ((a, b, c, d), (a, b, c, d), (a, b, c, d)) Source #

class RightReductiveMonoid m => RightGCDMonoid m where Source #

Class of monoids capable of finding the equivalent of greatest common divisor on the right side of two monoidal values. The methods' complexity must be no worse than linear in the length of the common suffix. The following laws must be respected:

stripCommonSuffix a b == (a', b', s)
   where s = commonSuffix a b
         Just a' = stripSuffix p a
         Just b' = stripSuffix p b
s == commonSuffix a b && a' <> s == a && b' <> s == b
   where (a', b', s) = stripCommonSuffix a b

Minimal complete definition

commonSuffix | stripCommonSuffix

Methods

commonSuffix :: m -> m -> m Source #

stripCommonSuffix :: m -> m -> (m, m, m) Source #

Instances
RightGCDMonoid () Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

commonSuffix :: () -> () -> () Source #

stripCommonSuffix :: () -> () -> ((), (), ()) Source #

RightGCDMonoid ByteString Source # 
Instance details

Defined in Data.Monoid.Cancellative

RightGCDMonoid ByteString Source # 
Instance details

Defined in Data.Monoid.Cancellative

RightGCDMonoid IntSet Source # 
Instance details

Defined in Data.Monoid.Cancellative

RightGCDMonoid x => RightGCDMonoid (Maybe x) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

commonSuffix :: Maybe x -> Maybe x -> Maybe x Source #

stripCommonSuffix :: Maybe x -> Maybe x -> (Maybe x, Maybe x, Maybe x) Source #

LeftGCDMonoid a => RightGCDMonoid (Dual a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

commonSuffix :: Dual a -> Dual a -> Dual a Source #

stripCommonSuffix :: Dual a -> Dual a -> (Dual a, Dual a, Dual a) Source #

(Integral a, Ord a) => RightGCDMonoid (Sum a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

commonSuffix :: Sum a -> Sum a -> Sum a Source #

stripCommonSuffix :: Sum a -> Sum a -> (Sum a, Sum a, Sum a) Source #

Integral a => RightGCDMonoid (Product a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Eq a => RightGCDMonoid (Seq a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

commonSuffix :: Seq a -> Seq a -> Seq a Source #

stripCommonSuffix :: Seq a -> Seq a -> (Seq a, Seq a, Seq a) Source #

Ord a => RightGCDMonoid (Set a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

commonSuffix :: Set a -> Set a -> Set a Source #

stripCommonSuffix :: Set a -> Set a -> (Set a, Set a, Set a) Source #

Eq a => RightGCDMonoid (Vector a) Source # 
Instance details

Defined in Data.Monoid.Cancellative

(StableFactorialMonoid m, TextualMonoid m, RightGCDMonoid m) => RightGCDMonoid (LinePositioned m) Source # 
Instance details

Defined in Data.Monoid.Instances.Positioned

(StableFactorialMonoid m, RightGCDMonoid m) => RightGCDMonoid (OffsetPositioned m) Source # 
Instance details

Defined in Data.Monoid.Instances.Positioned

(RightGCDMonoid a, StableFactorialMonoid a) => RightGCDMonoid (Measured a) Source # 
Instance details

Defined in Data.Monoid.Instances.Measured

(RightGCDMonoid a, StableFactorialMonoid a) => RightGCDMonoid (Concat a) Source # 
Instance details

Defined in Data.Monoid.Instances.Concat

(RightGCDMonoid a, RightGCDMonoid b) => RightGCDMonoid (a, b) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

commonSuffix :: (a, b) -> (a, b) -> (a, b) Source #

stripCommonSuffix :: (a, b) -> (a, b) -> ((a, b), (a, b), (a, b)) Source #

(RightGCDMonoid a, RightGCDMonoid b) => RightGCDMonoid (Stateful a b) Source # 
Instance details

Defined in Data.Monoid.Instances.Stateful

Methods

commonSuffix :: Stateful a b -> Stateful a b -> Stateful a b Source #

stripCommonSuffix :: Stateful a b -> Stateful a b -> (Stateful a b, Stateful a b, Stateful a b) Source #

(RightGCDMonoid a, RightGCDMonoid b, RightGCDMonoid c) => RightGCDMonoid (a, b, c) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

commonSuffix :: (a, b, c) -> (a, b, c) -> (a, b, c) Source #

stripCommonSuffix :: (a, b, c) -> (a, b, c) -> ((a, b, c), (a, b, c), (a, b, c)) Source #

(RightGCDMonoid a, RightGCDMonoid b, RightGCDMonoid c, RightGCDMonoid d) => RightGCDMonoid (a, b, c, d) Source # 
Instance details

Defined in Data.Monoid.Cancellative

Methods

commonSuffix :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) Source #

stripCommonSuffix :: (a, b, c, d) -> (a, b, c, d) -> ((a, b, c, d), (a, b, c, d), (a, b, c, d)) Source #