monoid-subclasses-0.3.4: Subclasses of Monoid

Safe HaskellNone

Data.Monoid.Factorial

Contents

Description

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

Synopsis

Classes

class MonoidNull m => FactorialMonoid m whereSource

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
 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)

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

Methods

factors :: m -> [m]Source

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

primePrefix :: m -> mSource

The prime prefix, mempty if none.

primeSuffix :: m -> mSource

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.

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

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

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

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

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

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

length :: m -> IntSource

The length of the list of primes.

foldMap :: (FactorialMonoid m, Monoid n) => (m -> n) -> m -> nSource

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 :: FactorialMonoid m => (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 :: FactorialMonoid m => (m -> Bool) -> m -> mSource

Equivalent to takeWhile from Data.List.

dropWhile :: FactorialMonoid m => (m -> Bool) -> m -> mSource

Equivalent to dropWhile from Data.List.

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

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

drop :: FactorialMonoid m => Int -> m -> mSource

Equivalent to drop from Data.List.

take :: FactorialMonoid m => Int -> m -> mSource

Equivalent to take from Data.List.

reverse :: FactorialMonoid m => m -> mSource

Equivalent to reverse from Data.List.

Monad function equivalents

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

A mapM equivalent.

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

A mapM_ equivalent.