| Safe Haskell | Trustworthy | 
|---|---|
| Language | Haskell2010 | 
Data.Monoid.Factorial
Description
This module defines the FactorialMonoid class and some of its instances.
- class MonoidNull m => FactorialMonoid m where- factors :: m -> [m]
- primePrefix :: m -> m
- primeSuffix :: m -> m
- splitPrimePrefix :: m -> Maybe (m, m)
- splitPrimeSuffix :: m -> Maybe (m, m)
- inits :: m -> [m]
- tails :: m -> [m]
- foldl :: (a -> m -> a) -> a -> m -> a
- foldl' :: (a -> m -> a) -> a -> m -> a
- foldr :: (m -> a -> a) -> a -> m -> a
- length :: m -> Int
- foldMap :: Monoid n => (m -> n) -> m -> n
- span :: (m -> Bool) -> m -> (m, m)
- break :: (m -> Bool) -> m -> (m, m)
- split :: (m -> Bool) -> m -> [m]
- takeWhile :: (m -> Bool) -> m -> m
- dropWhile :: (m -> Bool) -> m -> m
- spanMaybe :: s -> (s -> m -> Maybe s) -> m -> (m, m, s)
- spanMaybe' :: s -> (s -> m -> Maybe s) -> m -> (m, m, s)
- splitAt :: Int -> m -> (m, m)
- drop :: Int -> m -> m
- take :: Int -> m -> m
- reverse :: m -> m
 
- class (FactorialMonoid m, PositiveMonoid m) => StableFactorialMonoid m
- mapM :: (FactorialMonoid a, Monoid b, Monad m) => (a -> m b) -> a -> m b
- mapM_ :: (FactorialMonoid a, Monad m) => (a -> m b) -> a -> m ()
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.tails . 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 <> suffixA minimal instance definition must implement factors or splitPrimePrefix. Other methods are provided and should
 be implemented only for performance reasons.
Minimal complete definition
Methods
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
splitPrimeSuffix :: m -> Maybe (m, m) Source
Returns the list of all prefixes of the argument, mempty first.
Returns the list of all suffixes of the argument, mempty last.
foldl :: (a -> m -> a) -> a -> m -> a Source
foldl' :: (a -> m -> a) -> a -> m -> a Source
foldr :: (m -> a -> a) -> a -> m -> a 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
break :: (m -> Bool) -> m -> (m, m) Source
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
dropWhile :: (m -> Bool) -> m -> m Source
spanMaybe :: s -> (s -> m -> Maybe s) -> m -> (m, m, s) Source
spanMaybe' :: s -> (s -> m -> Maybe s) -> m -> (m, m, s) Source
Strict version of spanMaybe.
Instances
| FactorialMonoid () | |
| FactorialMonoid ByteString | |
| FactorialMonoid ByteString | |
| FactorialMonoid IntSet | |
| FactorialMonoid Text | |
| FactorialMonoid Text | |
| FactorialMonoid ByteStringUTF8 | |
| FactorialMonoid [x] | |
| FactorialMonoid a => FactorialMonoid (Dual a) | |
| (Integral a, Eq a) => FactorialMonoid (Sum a) | |
| Integral a => FactorialMonoid (Product a) | |
| FactorialMonoid a => FactorialMonoid (Maybe a) | |
| FactorialMonoid (IntMap a) | |
| Ord a => FactorialMonoid (Set a) | |
| FactorialMonoid (Seq a) | |
| FactorialMonoid (Vector a) | |
| FactorialMonoid a => FactorialMonoid (Concat a) | |
| StableFactorialMonoid a => FactorialMonoid (Measured a) | |
| (StableFactorialMonoid m, TextualMonoid m) => FactorialMonoid (LinePositioned m) | |
| StableFactorialMonoid m => FactorialMonoid (OffsetPositioned m) | |
| (FactorialMonoid a, FactorialMonoid b) => FactorialMonoid (a, b) | |
| Ord k => FactorialMonoid (Map k v) | |
| (FactorialMonoid a, FactorialMonoid b) => FactorialMonoid (Stateful a b) | 
class (FactorialMonoid m, PositiveMonoid m) => StableFactorialMonoid m Source
A subclass of FactorialMonoid whose instances satisfy this additional law:
factors (a <> b) == factors a <> factors b
Instances
Monad function equivalents
mapM_ :: (FactorialMonoid a, Monad m) => (a -> m b) -> a -> m () Source
A mapM_ equivalent.