monoid-subclasses-1.0.1: Subclasses of Monoid

Safe HaskellTrustworthy
LanguageHaskell2010

Data.Monoid.GCD

Description

This module defines the GCDMonoid subclass of the Monoid class.

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.

The GCDMonoid class is for Abelian, i.e., Commutative monoids. Since most practical monoids in Haskell are not Abelian, there are also its three symmetric superclasses:

Synopsis

Documentation

class (Monoid m, Commutative m, Reductive m, LeftGCDMonoid m, RightGCDMonoid m, OverlappingGCDMonoid m) => GCDMonoid m where Source #

Class of Abelian monoids that allow the greatest common divisor 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 Cancellative, 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

Methods

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

Instances
GCDMonoid () Source #

O(1)

Instance details

Defined in Data.Monoid.GCD

Methods

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

GCDMonoid IntSet Source #

O(m+n)

Instance details

Defined in Data.Monoid.GCD

Methods

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

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

Defined in Data.Monoid.GCD

Methods

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

GCDMonoid (Sum Natural) Source #

O(1)

Instance details

Defined in Data.Monoid.GCD

GCDMonoid (Product Natural) Source #

O(1)

Instance details

Defined in Data.Monoid.GCD

Ord a => GCDMonoid (Set a) Source #

O(m*log(n/m + 1)), m <= n

Instance details

Defined in Data.Monoid.GCD

Methods

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

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

Defined in Data.Monoid.GCD

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.GCD

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.GCD

Methods

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

class (Monoid m, LeftReductive 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 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

Furthermore, commonPrefix must return the unique greatest common prefix that contains, as its prefix, any other prefix x of both values:

not (x `isPrefixOf` a && x `isPrefixOf` b) || x `isPrefixOf` commonPrefix a b

and it cannot itself be a suffix of any other common prefix y of both values:

not (y `isPrefixOf` a && y `isPrefixOf` b && commonPrefix a b `isSuffixOf` y)

Minimal complete definition

commonPrefix | stripCommonPrefix

Methods

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

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

Instances
LeftGCDMonoid () Source #

O(1)

Instance details

Defined in Data.Monoid.GCD

Methods

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

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

LeftGCDMonoid ByteString Source #

O(prefixLength)

Instance details

Defined in Data.Monoid.GCD

LeftGCDMonoid ByteString Source #

O(prefixLength)

Instance details

Defined in Data.Monoid.GCD

LeftGCDMonoid IntSet Source #

O(m+n)

Instance details

Defined in Data.Monoid.GCD

LeftGCDMonoid Text Source #

O(prefixLength)

Instance details

Defined in Data.Monoid.GCD

LeftGCDMonoid Text Source #

O(prefixLength)

Instance details

Defined in Data.Monoid.GCD

LeftGCDMonoid ByteStringUTF8 Source #

O(prefixLength)

Instance details

Defined in Data.Monoid.Instances.ByteString.UTF8

Eq x => LeftGCDMonoid [x] Source #

O(prefixLength)

Instance details

Defined in Data.Monoid.GCD

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.GCD

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.GCD

Methods

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

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

LeftGCDMonoid (Sum Natural) Source #

O(1)

Instance details

Defined in Data.Monoid.GCD

LeftGCDMonoid (Product Natural) Source #

O(1)

Instance details

Defined in Data.Monoid.GCD

Eq a => LeftGCDMonoid (IntMap a) Source #

O(m+n)

Instance details

Defined in Data.Monoid.GCD

Eq a => LeftGCDMonoid (Seq a) Source #

O(prefixLength)

Instance details

Defined in Data.Monoid.GCD

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 #

O(m*log(n/m + 1)), m <= n

Instance details

Defined in Data.Monoid.GCD

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 #

O(prefixLength)

Instance details

Defined in Data.Monoid.GCD

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

Defined in Data.Monoid.Instances.Positioned

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

Defined in Data.Monoid.Instances.Positioned

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

Defined in Data.Monoid.Instances.Measured

(LeftGCDMonoid a, StableFactorial a, PositiveMonoid 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.GCD

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 #

O(m+n)

Instance details

Defined in Data.Monoid.GCD

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.GCD

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.GCD

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 (Monoid m, RightReductive 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 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

Furthermore, commonSuffix must return the unique greatest common suffix that contains, as its suffix, any other suffix x of both values:

not (x `isSuffixOf` a && x `isSuffixOf` b) || x `isSuffixOf` commonSuffix a b

and it cannot itself be a prefix of any other common suffix y of both values:

not (y `isSuffixOf` a && y `isSuffixOf` b && commonSuffix a b `isPrefixOf` y)

Minimal complete definition

commonSuffix | stripCommonSuffix

Methods

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

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

Instances
RightGCDMonoid () Source #

O(1)

Instance details

Defined in Data.Monoid.GCD

Methods

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

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

RightGCDMonoid ByteString Source #

O(suffixLength)

Instance details

Defined in Data.Monoid.GCD

RightGCDMonoid ByteString Source #

O(suffixLength)

Instance details

Defined in Data.Monoid.GCD

RightGCDMonoid IntSet Source #

O(m+n)

Instance details

Defined in Data.Monoid.GCD

RightGCDMonoid Text Source #

O(m+n)

Since: 1.0

Instance details

Defined in Data.Monoid.GCD

RightGCDMonoid Text Source #

O(suffixLength)

Since: 1.0

Instance details

Defined in Data.Monoid.GCD

Eq x => RightGCDMonoid [x] Source #

O(m+n)

Since: 1.0

Instance details

Defined in Data.Monoid.GCD

Methods

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

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

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

Defined in Data.Monoid.GCD

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.GCD

Methods

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

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

RightGCDMonoid (Sum Natural) Source #

O(1)

Instance details

Defined in Data.Monoid.GCD

RightGCDMonoid (Product Natural) Source #

O(1)

Instance details

Defined in Data.Monoid.GCD

Eq a => RightGCDMonoid (Seq a) Source #

O(suffixLength)

Instance details

Defined in Data.Monoid.GCD

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 #

O(m*log(n/m + 1)), m <= n

Instance details

Defined in Data.Monoid.GCD

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 #

O(suffixLength)

Instance details

Defined in Data.Monoid.GCD

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

Defined in Data.Monoid.Instances.Positioned

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

Defined in Data.Monoid.Instances.Positioned

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

Defined in Data.Monoid.Instances.Measured

(RightGCDMonoid a, StableFactorial a, PositiveMonoid 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.GCD

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.GCD

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.GCD

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 #

class (Monoid m, LeftReductive m, RightReductive m) => OverlappingGCDMonoid m where Source #

Class of monoids for which the greatest overlap can be found between any two values, such that

a == a' <> overlap a b
b == overlap a b <> b'

The methods must satisfy the following laws:

stripOverlap a b == (stripSuffixOverlap b a, overlap a b, stripPrefixOverlap a b)
stripSuffixOverlap b a <> overlap a b == a
overlap a b <> stripPrefixOverlap a b == b

The result of overlap a b must be the largest prefix of b and suffix of a, in the sense that it is contained in any other value x that satifies the property (x isPrefixOf b) && (x isSuffixOf a):

(x `isPrefixOf` overlap a b) && (x `isSuffixOf` overlap a b)

and it must be unique so it's not contained in any other value y that satisfies the same property (y isPrefixOf b) && (y isSuffixOf a):

not ((y `isPrefixOf` overlap a b) && (y `isSuffixOf` overlap a b) && y /= overlap a b)

Since: 1.0

Minimal complete definition

stripOverlap

Methods

stripPrefixOverlap :: m -> m -> m Source #

stripSuffixOverlap :: m -> m -> m Source #

overlap :: m -> m -> m Source #

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

Instances
OverlappingGCDMonoid () Source #

O(1)

Instance details

Defined in Data.Monoid.Monus

Methods

stripPrefixOverlap :: () -> () -> () Source #

stripSuffixOverlap :: () -> () -> () Source #

overlap :: () -> () -> () Source #

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

OverlappingGCDMonoid ByteString Source #

O(m*n)

Instance details

Defined in Data.Monoid.Monus

OverlappingGCDMonoid ByteString Source #

O(min(m,n)^2)

Instance details

Defined in Data.Monoid.Monus

OverlappingGCDMonoid IntSet Source #

O(m+n)

Instance details

Defined in Data.Monoid.Monus

OverlappingGCDMonoid Text Source #

O(m*n)

Instance details

Defined in Data.Monoid.Monus

OverlappingGCDMonoid Text Source #

O(min(m,n)^2)

Instance details

Defined in Data.Monoid.Monus

Eq a => OverlappingGCDMonoid [a] Source #

O(m*n)

Instance details

Defined in Data.Monoid.Monus

Methods

stripPrefixOverlap :: [a] -> [a] -> [a] Source #

stripSuffixOverlap :: [a] -> [a] -> [a] Source #

overlap :: [a] -> [a] -> [a] Source #

stripOverlap :: [a] -> [a] -> ([a], [a], [a]) Source #

(OverlappingGCDMonoid a, MonoidNull a) => OverlappingGCDMonoid (Maybe a) Source # 
Instance details

Defined in Data.Monoid.Monus

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

Defined in Data.Monoid.Monus

Methods

stripPrefixOverlap :: Dual a -> Dual a -> Dual a Source #

stripSuffixOverlap :: Dual a -> Dual a -> Dual a Source #

overlap :: Dual a -> Dual a -> Dual a Source #

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

OverlappingGCDMonoid (Sum Natural) Source #

O(1)

Instance details

Defined in Data.Monoid.Monus

OverlappingGCDMonoid (Product Natural) Source #

O(1)

Instance details

Defined in Data.Monoid.Monus

Eq a => OverlappingGCDMonoid (IntMap a) Source #

O(m+n)

Instance details

Defined in Data.Monoid.Monus

Eq a => OverlappingGCDMonoid (Seq a) Source #

O(min(m,n)^2)

Instance details

Defined in Data.Monoid.Monus

Methods

stripPrefixOverlap :: Seq a -> Seq a -> Seq a Source #

stripSuffixOverlap :: Seq a -> Seq a -> Seq a Source #

overlap :: Seq a -> Seq a -> Seq a Source #

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

Ord a => OverlappingGCDMonoid (Set a) Source #

O(m*log(nm + 1)), m <= n/

Instance details

Defined in Data.Monoid.Monus

Methods

stripPrefixOverlap :: Set a -> Set a -> Set a Source #

stripSuffixOverlap :: Set a -> Set a -> Set a Source #

overlap :: Set a -> Set a -> Set a Source #

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

Eq a => OverlappingGCDMonoid (Vector a) Source #

O(min(m,n)^2)

Instance details

Defined in Data.Monoid.Monus

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

Defined in Data.Monoid.Monus

Methods

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

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

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

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

(Ord k, Eq v) => OverlappingGCDMonoid (Map k v) Source #

O(m+n)

Instance details

Defined in Data.Monoid.Monus

Methods

stripPrefixOverlap :: Map k v -> Map k v -> Map k v Source #

stripSuffixOverlap :: Map k v -> Map k v -> Map k v Source #

overlap :: Map k v -> Map k v -> Map k v Source #

stripOverlap :: Map k v -> Map k v -> (Map k v, Map k v, Map k v) Source #

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

Defined in Data.Monoid.Monus

Methods

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

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

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

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

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

Defined in Data.Monoid.Monus

Methods

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

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

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

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