Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
This module defines the FactorialMonoid
class and some of its instances.
Synopsis
- module Data.Semigroup.Factorial
- class (Factorial m, MonoidNull m) => FactorialMonoid m where
- splitPrimePrefix :: m -> Maybe (m, m)
- splitPrimeSuffix :: m -> Maybe (m, m)
- inits :: m -> [m]
- tails :: m -> [m]
- 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
- type StableFactorialMonoid m = (StableFactorial m, FactorialMonoid m, PositiveMonoid m)
Documentation
module Data.Semigroup.Factorial
class (Factorial m, 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 in addition to those of Factorial
:
null == List.null . 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 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 should implement splitPrimePrefix
for performance reasons, and other methods where
beneficial.
Nothing
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.
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
.
splitAt :: Int -> m -> (m, m) Source #
Instances
type StableFactorialMonoid m = (StableFactorial m, FactorialMonoid m, PositiveMonoid m) Source #
Deprecated: Use Data.Semigroup.Factorial.StableFactorial instead.