Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
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
- class (Monoid m, Commutative m, Reductive m, LeftGCDMonoid m, RightGCDMonoid m, OverlappingGCDMonoid m) => GCDMonoid m where
- gcd :: m -> m -> m
- class (Monoid m, LeftReductive m) => LeftGCDMonoid m where
- commonPrefix :: m -> m -> m
- stripCommonPrefix :: m -> m -> (m, m, m)
- class (Monoid m, RightReductive m) => RightGCDMonoid m where
- commonSuffix :: m -> m -> m
- stripCommonSuffix :: m -> m -> (m, m, m)
- class (Monoid m, LeftReductive m, RightReductive m) => OverlappingGCDMonoid m where
- stripPrefixOverlap :: m -> m -> m
- stripSuffixOverlap :: m -> m -> m
- overlap :: m -> m -> m
- stripOverlap :: m -> m -> (m, m, m)
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
Instances
GCDMonoid () Source # | O(1) |
Defined in Data.Monoid.GCD | |
GCDMonoid IntSet Source # | O(m+n) |
GCDMonoid a => GCDMonoid (Dual a) Source # | |
GCDMonoid (Sum Natural) Source # | O(1) |
GCDMonoid (Product Natural) Source # | O(1) |
Ord a => GCDMonoid (Set a) Source # | O(m*log(n/m + 1)), m <= n |
(GCDMonoid a, GCDMonoid b) => GCDMonoid (a, b) Source # | |
Defined in Data.Monoid.GCD | |
(GCDMonoid a, GCDMonoid b, GCDMonoid c) => GCDMonoid (a, b, c) Source # | |
Defined in Data.Monoid.GCD | |
(GCDMonoid a, GCDMonoid b, GCDMonoid c, GCDMonoid d) => GCDMonoid (a, b, c, d) Source # | |
Defined in Data.Monoid.GCD |
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)
commonPrefix :: m -> m -> m Source #
stripCommonPrefix :: m -> m -> (m, m, m) Source #
Instances
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)
commonSuffix :: m -> m -> m Source #
stripCommonSuffix :: m -> m -> (m, m, m) Source #
Instances
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
stripPrefixOverlap :: m -> m -> m Source #
stripSuffixOverlap :: m -> m -> m Source #
overlap :: m -> m -> m Source #
stripOverlap :: m -> m -> (m, m, m) Source #