incremental-parser-0.2.1: Generic parser library capable of providing partial results from partial input.

Safe HaskellSafe-Infered

Data.Monoid.Factorial

Contents

Description

This module defines the FactorialMonoid class.

Synopsis

Classes

class Monoid m => FactorialMonoid m whereSource

Class of monoids that can be split into irreducible factors, i.e., atoms or primes. The methods of this class satisfy the following laws:

 mconcat . factors == id
 factors mempty == []
 all (\f-> factors f == [f]) (factors m)
 factors == unfoldr splitPrimePrefix == reverse . unfoldr (fmap swap . splitPrimeSuffix)
 primePrefix == maybe mempty fst . splitPrimePrefix
 primeSuffix == maybe mempty snd . splitPrimeSuffix
 mfoldl f f0 == foldl f f0 . factors
 mfoldr f f0 == foldr f f0 . factors
 mspan p m == (mconcat l, mconcat r) where (l, r) = span p (factors m)

A minimal instance definition must implement factors or splitPrimePrefix.

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.

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

Like foldl on the list of primes.

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

Like foldr on the list of primes.

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

Like span on the list of primes.

Functions

mbreak :: FactorialMonoid m => (m -> Bool) -> m -> (m, m)Source

A break equivalent.

mlength :: FactorialMonoid m => m -> IntSource

A length equivalent.

mmap :: FactorialMonoid m => (m -> m) -> m -> mSource

A map equivalent.

mreverse :: FactorialMonoid m => m -> mSource

A reverse equivalent.

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

A takeWhile equivalent.

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

A dropWhile equivalent.