monoid-subclasses-1.0.1: Subclasses of Monoid

Safe HaskellTrustworthy
LanguageHaskell2010

Data.Monoid.Monus

Description

This module defines the OverlappingGCDMonoid => Monus subclass of the Monoid class.

Since: 1.0

Synopsis

Documentation

class (Commutative m, Monoid m, OverlappingGCDMonoid m) => Monus m where Source #

Class of Abelian monoids with monus. The monus operation <\> is a synonym for both stripPrefixOverlap and stripSuffixOverlap, which must be equivalent as <> is both associative and commutative:

(<\>) = flip stripPrefixOverlap
(<\>) = flip stripSuffixOverlap

Since: 1.0

Methods

(<\>) :: m -> m -> m infix 5 Source #

Instances
Monus () Source #

O(1)

Instance details

Defined in Data.Monoid.Monus

Methods

(<\>) :: () -> () -> () Source #

Monus IntSet Source #

O(m+n)

Instance details

Defined in Data.Monoid.Monus

Methods

(<\>) :: IntSet -> IntSet -> IntSet Source #

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

Defined in Data.Monoid.Monus

Methods

(<\>) :: Maybe a -> Maybe a -> Maybe a Source #

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

Defined in Data.Monoid.Monus

Methods

(<\>) :: Dual a -> Dual a -> Dual a Source #

Monus (Sum Natural) Source #

O(1)

Instance details

Defined in Data.Monoid.Monus

Monus (Product Natural) Source #

O(1)

Instance details

Defined in Data.Monoid.Monus

Ord a => Monus (Set a) Source #

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

Instance details

Defined in Data.Monoid.Monus

Methods

(<\>) :: Set a -> Set a -> Set a Source #

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

Defined in Data.Monoid.Monus

Methods

(<\>) :: (a, b) -> (a, b) -> (a, b) Source #

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

Defined in Data.Monoid.Monus

Methods

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

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

Defined in Data.Monoid.Monus

Methods

(<\>) :: (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 #