monoid-subclasses-0.4.2.1: Subclasses of Monoid

Safe HaskellTrustworthy
LanguageHaskell2010

Data.Monoid.Factorial

Contents

Description

This module defines the FactorialMonoid class and some of its instances.

Synopsis

Classes

class MonoidNull m => FactorialMonoid m where Source

Class of monoids that can be split into irreducible (i.e., atomic or prime) factors in a unique way. Factors of a Product are literally its prime factors:

factors (Product 12) == [Product 2, Product 2, Product 3]

Factors of a list are not its elements but all its single-item sublists:

factors "abc" == ["a", "b", "c"]

The methods of this class satisfy the following laws:

mconcat . factors == id
null == List.null . factors
List.all (\prime-> factors prime == [prime]) . factors
factors == unfoldr splitPrimePrefix == List.reverse . unfoldr (fmap swap . splitPrimeSuffix)
reverse == mconcat . List.reverse . factors
primePrefix == maybe mempty fst . splitPrimePrefix
primeSuffix == maybe mempty snd . splitPrimeSuffix
inits == List.map mconcat . List.inits . factors
tails == List.map mconcat . List.tails . factors
foldl f a == List.foldl f a . factors
foldl' f a == List.foldl' f a . factors
foldr f a == List.foldr f a . factors
span p m == (mconcat l, mconcat r) where (l, r) = List.span p (factors m)
List.all (List.all (not . pred) . factors) . split pred
mconcat . intersperse prime . split (== prime) == id
splitAt i m == (mconcat l, mconcat r) where (l, r) = List.splitAt i (factors m)
spanMaybe () (const $ bool Nothing (Maybe ()) . p) m == (takeWhile p m, dropWhile p m, ())
spanMaybe s0 (\s m-> Just $ f s m) m0 == (m0, mempty, foldl f s0 m0)
let (prefix, suffix, s') = spanMaybe s f m
    foldMaybe = foldl g (Just s)
    g s m = s >>= flip f m
in all ((Nothing ==) . foldMaybe) (inits prefix)
   && prefix == last (filter (isJust . foldMaybe) $ inits m)
   && Just s' == foldMaybe prefix
   && m == prefix <> suffix

A minimal instance definition must implement factors or splitPrimePrefix. Other methods are provided and should be implemented only for performance reasons.

Minimal complete definition

factors | splitPrimePrefix

Methods

factors :: m -> [m] Source

Returns a list of all prime factors; inverse of mconcat.

primePrefix :: m -> m Source

The prime prefix, mempty if none.

primeSuffix :: m -> m Source

The prime suffix, mempty if none.

splitPrimePrefix :: m -> Maybe (m, m) Source

Splits the argument into its prime prefix and the remaining suffix. Returns Nothing for mempty.

splitPrimeSuffix :: m -> Maybe (m, m) Source

Splits the argument into its prime suffix and the remaining prefix. Returns Nothing for mempty.

inits :: m -> [m] Source

Returns the list of all prefixes of the argument, mempty first.

tails :: m -> [m] Source

Returns the list of all suffixes of the argument, mempty last.

foldl :: (a -> m -> a) -> a -> m -> a Source

Like foldl from Data.List on the list of primes.

foldl' :: (a -> m -> a) -> a -> m -> a Source

Like foldl' from Data.List on the list of primes.

foldr :: (m -> a -> a) -> a -> m -> a Source

Like foldr from Data.List on the list of primes.

length :: m -> Int Source

The length of the list of primes.

foldMap :: Monoid n => (m -> n) -> m -> n Source

Generalizes foldMap from Data.Foldable, except the function arguments are prime factors rather than the structure elements.

span :: (m -> Bool) -> m -> (m, m) Source

Like span from Data.List on the list of primes.

break :: (m -> Bool) -> m -> (m, m) Source

Equivalent to break from Data.List.

split :: (m -> Bool) -> m -> [m] Source

Splits the monoid into components delimited by prime separators satisfying the given predicate. The primes satisfying the predicate are not a part of the result.

takeWhile :: (m -> Bool) -> m -> m Source

Equivalent to takeWhile from Data.List.

dropWhile :: (m -> Bool) -> m -> m Source

Equivalent to dropWhile from Data.List.

spanMaybe :: s -> (s -> m -> Maybe s) -> m -> (m, m, s) Source

A stateful variant of span, threading the result of the test function as long as it returns Just.

spanMaybe' :: s -> (s -> m -> Maybe s) -> m -> (m, m, s) Source

Strict version of spanMaybe.

splitAt :: Int -> m -> (m, m) Source

Like splitAt from Data.List on the list of primes.

drop :: Int -> m -> m Source

Equivalent to drop from Data.List.

take :: Int -> m -> m Source

Equivalent to take from Data.List.

reverse :: m -> m Source

Equivalent to reverse from Data.List.

Monad function equivalents

mapM :: (FactorialMonoid a, Monoid b, Monad m) => (a -> m b) -> a -> m b Source

A mapM equivalent.

mapM_ :: (FactorialMonoid a, Monad m) => (a -> m b) -> a -> m () Source

A mapM_ equivalent.