monoid-subclasses-0.4.6.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.

Instances
FactorialMonoid () Source # 
Instance details

Defined in Data.Monoid.Factorial

Methods

factors :: () -> [()] Source #

primePrefix :: () -> () Source #

primeSuffix :: () -> () Source #

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

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

inits :: () -> [()] Source #

tails :: () -> [()] Source #

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

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

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

length :: () -> Int Source #

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

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

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

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

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

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

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

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

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

drop :: Int -> () -> () Source #

take :: Int -> () -> () Source #

reverse :: () -> () Source #

FactorialMonoid ByteString Source # 
Instance details

Defined in Data.Monoid.Factorial

FactorialMonoid ByteString Source # 
Instance details

Defined in Data.Monoid.Factorial

FactorialMonoid IntSet Source # 
Instance details

Defined in Data.Monoid.Factorial

FactorialMonoid Text Source # 
Instance details

Defined in Data.Monoid.Factorial

Methods

factors :: Text -> [Text] Source #

primePrefix :: Text -> Text Source #

primeSuffix :: Text -> Text Source #

splitPrimePrefix :: Text -> Maybe (Text, Text) Source #

splitPrimeSuffix :: Text -> Maybe (Text, Text) Source #

inits :: Text -> [Text] Source #

tails :: Text -> [Text] Source #

foldl :: (a -> Text -> a) -> a -> Text -> a Source #

foldl' :: (a -> Text -> a) -> a -> Text -> a Source #

foldr :: (Text -> a -> a) -> a -> Text -> a Source #

length :: Text -> Int Source #

foldMap :: Monoid n => (Text -> n) -> Text -> n Source #

span :: (Text -> Bool) -> Text -> (Text, Text) Source #

break :: (Text -> Bool) -> Text -> (Text, Text) Source #

split :: (Text -> Bool) -> Text -> [Text] Source #

takeWhile :: (Text -> Bool) -> Text -> Text Source #

dropWhile :: (Text -> Bool) -> Text -> Text Source #

spanMaybe :: s -> (s -> Text -> Maybe s) -> Text -> (Text, Text, s) Source #

spanMaybe' :: s -> (s -> Text -> Maybe s) -> Text -> (Text, Text, s) Source #

splitAt :: Int -> Text -> (Text, Text) Source #

drop :: Int -> Text -> Text Source #

take :: Int -> Text -> Text Source #

reverse :: Text -> Text Source #

FactorialMonoid Text Source # 
Instance details

Defined in Data.Monoid.Factorial

Methods

factors :: Text -> [Text] Source #

primePrefix :: Text -> Text Source #

primeSuffix :: Text -> Text Source #

splitPrimePrefix :: Text -> Maybe (Text, Text) Source #

splitPrimeSuffix :: Text -> Maybe (Text, Text) Source #

inits :: Text -> [Text] Source #

tails :: Text -> [Text] Source #

foldl :: (a -> Text -> a) -> a -> Text -> a Source #

foldl' :: (a -> Text -> a) -> a -> Text -> a Source #

foldr :: (Text -> a -> a) -> a -> Text -> a Source #

length :: Text -> Int Source #

foldMap :: Monoid n => (Text -> n) -> Text -> n Source #

span :: (Text -> Bool) -> Text -> (Text, Text) Source #

break :: (Text -> Bool) -> Text -> (Text, Text) Source #

split :: (Text -> Bool) -> Text -> [Text] Source #

takeWhile :: (Text -> Bool) -> Text -> Text Source #

dropWhile :: (Text -> Bool) -> Text -> Text Source #

spanMaybe :: s -> (s -> Text -> Maybe s) -> Text -> (Text, Text, s) Source #

spanMaybe' :: s -> (s -> Text -> Maybe s) -> Text -> (Text, Text, s) Source #

splitAt :: Int -> Text -> (Text, Text) Source #

drop :: Int -> Text -> Text Source #

take :: Int -> Text -> Text Source #

reverse :: Text -> Text Source #

FactorialMonoid ByteStringUTF8 Source # 
Instance details

Defined in Data.Monoid.Instances.ByteString.UTF8

Methods

factors :: ByteStringUTF8 -> [ByteStringUTF8] Source #

primePrefix :: ByteStringUTF8 -> ByteStringUTF8 Source #

primeSuffix :: ByteStringUTF8 -> ByteStringUTF8 Source #

splitPrimePrefix :: ByteStringUTF8 -> Maybe (ByteStringUTF8, ByteStringUTF8) Source #

splitPrimeSuffix :: ByteStringUTF8 -> Maybe (ByteStringUTF8, ByteStringUTF8) Source #

inits :: ByteStringUTF8 -> [ByteStringUTF8] Source #

tails :: ByteStringUTF8 -> [ByteStringUTF8] Source #

foldl :: (a -> ByteStringUTF8 -> a) -> a -> ByteStringUTF8 -> a Source #

foldl' :: (a -> ByteStringUTF8 -> a) -> a -> ByteStringUTF8 -> a Source #

foldr :: (ByteStringUTF8 -> a -> a) -> a -> ByteStringUTF8 -> a Source #

length :: ByteStringUTF8 -> Int Source #

foldMap :: Monoid n => (ByteStringUTF8 -> n) -> ByteStringUTF8 -> n Source #

span :: (ByteStringUTF8 -> Bool) -> ByteStringUTF8 -> (ByteStringUTF8, ByteStringUTF8) Source #

break :: (ByteStringUTF8 -> Bool) -> ByteStringUTF8 -> (ByteStringUTF8, ByteStringUTF8) Source #

split :: (ByteStringUTF8 -> Bool) -> ByteStringUTF8 -> [ByteStringUTF8] Source #

takeWhile :: (ByteStringUTF8 -> Bool) -> ByteStringUTF8 -> ByteStringUTF8 Source #

dropWhile :: (ByteStringUTF8 -> Bool) -> ByteStringUTF8 -> ByteStringUTF8 Source #

spanMaybe :: s -> (s -> ByteStringUTF8 -> Maybe s) -> ByteStringUTF8 -> (ByteStringUTF8, ByteStringUTF8, s) Source #

spanMaybe' :: s -> (s -> ByteStringUTF8 -> Maybe s) -> ByteStringUTF8 -> (ByteStringUTF8, ByteStringUTF8, s) Source #

splitAt :: Int -> ByteStringUTF8 -> (ByteStringUTF8, ByteStringUTF8) Source #

drop :: Int -> ByteStringUTF8 -> ByteStringUTF8 Source #

take :: Int -> ByteStringUTF8 -> ByteStringUTF8 Source #

reverse :: ByteStringUTF8 -> ByteStringUTF8 Source #

FactorialMonoid [x] Source # 
Instance details

Defined in Data.Monoid.Factorial

Methods

factors :: [x] -> [[x]] Source #

primePrefix :: [x] -> [x] Source #

primeSuffix :: [x] -> [x] Source #

splitPrimePrefix :: [x] -> Maybe ([x], [x]) Source #

splitPrimeSuffix :: [x] -> Maybe ([x], [x]) Source #

inits :: [x] -> [[x]] Source #

tails :: [x] -> [[x]] Source #

foldl :: (a -> [x] -> a) -> a -> [x] -> a Source #

foldl' :: (a -> [x] -> a) -> a -> [x] -> a Source #

foldr :: ([x] -> a -> a) -> a -> [x] -> a Source #

length :: [x] -> Int Source #

foldMap :: Monoid n => ([x] -> n) -> [x] -> n Source #

span :: ([x] -> Bool) -> [x] -> ([x], [x]) Source #

break :: ([x] -> Bool) -> [x] -> ([x], [x]) Source #

split :: ([x] -> Bool) -> [x] -> [[x]] Source #

takeWhile :: ([x] -> Bool) -> [x] -> [x] Source #

dropWhile :: ([x] -> Bool) -> [x] -> [x] Source #

spanMaybe :: s -> (s -> [x] -> Maybe s) -> [x] -> ([x], [x], s) Source #

spanMaybe' :: s -> (s -> [x] -> Maybe s) -> [x] -> ([x], [x], s) Source #

splitAt :: Int -> [x] -> ([x], [x]) Source #

drop :: Int -> [x] -> [x] Source #

take :: Int -> [x] -> [x] Source #

reverse :: [x] -> [x] Source #

FactorialMonoid a => FactorialMonoid (Maybe a) Source # 
Instance details

Defined in Data.Monoid.Factorial

Methods

factors :: Maybe a -> [Maybe a] Source #

primePrefix :: Maybe a -> Maybe a Source #

primeSuffix :: Maybe a -> Maybe a Source #

splitPrimePrefix :: Maybe a -> Maybe (Maybe a, Maybe a) Source #

splitPrimeSuffix :: Maybe a -> Maybe (Maybe a, Maybe a) Source #

inits :: Maybe a -> [Maybe a] Source #

tails :: Maybe a -> [Maybe a] Source #

foldl :: (a0 -> Maybe a -> a0) -> a0 -> Maybe a -> a0 Source #

foldl' :: (a0 -> Maybe a -> a0) -> a0 -> Maybe a -> a0 Source #

foldr :: (Maybe a -> a0 -> a0) -> a0 -> Maybe a -> a0 Source #

length :: Maybe a -> Int Source #

foldMap :: Monoid n => (Maybe a -> n) -> Maybe a -> n Source #

span :: (Maybe a -> Bool) -> Maybe a -> (Maybe a, Maybe a) Source #

break :: (Maybe a -> Bool) -> Maybe a -> (Maybe a, Maybe a) Source #

split :: (Maybe a -> Bool) -> Maybe a -> [Maybe a] Source #

takeWhile :: (Maybe a -> Bool) -> Maybe a -> Maybe a Source #

dropWhile :: (Maybe a -> Bool) -> Maybe a -> Maybe a Source #

spanMaybe :: s -> (s -> Maybe a -> Maybe s) -> Maybe a -> (Maybe a, Maybe a, s) Source #

spanMaybe' :: s -> (s -> Maybe a -> Maybe s) -> Maybe a -> (Maybe a, Maybe a, s) Source #

splitAt :: Int -> Maybe a -> (Maybe a, Maybe a) Source #

drop :: Int -> Maybe a -> Maybe a Source #

take :: Int -> Maybe a -> Maybe a Source #

reverse :: Maybe a -> Maybe a Source #

FactorialMonoid a => FactorialMonoid (Dual a) Source # 
Instance details

Defined in Data.Monoid.Factorial

Methods

factors :: Dual a -> [Dual a] Source #

primePrefix :: Dual a -> Dual a Source #

primeSuffix :: Dual a -> Dual a Source #

splitPrimePrefix :: Dual a -> Maybe (Dual a, Dual a) Source #

splitPrimeSuffix :: Dual a -> Maybe (Dual a, Dual a) Source #

inits :: Dual a -> [Dual a] Source #

tails :: Dual a -> [Dual a] Source #

foldl :: (a0 -> Dual a -> a0) -> a0 -> Dual a -> a0 Source #

foldl' :: (a0 -> Dual a -> a0) -> a0 -> Dual a -> a0 Source #

foldr :: (Dual a -> a0 -> a0) -> a0 -> Dual a -> a0 Source #

length :: Dual a -> Int Source #

foldMap :: Monoid n => (Dual a -> n) -> Dual a -> n Source #

span :: (Dual a -> Bool) -> Dual a -> (Dual a, Dual a) Source #

break :: (Dual a -> Bool) -> Dual a -> (Dual a, Dual a) Source #

split :: (Dual a -> Bool) -> Dual a -> [Dual a] Source #

takeWhile :: (Dual a -> Bool) -> Dual a -> Dual a Source #

dropWhile :: (Dual a -> Bool) -> Dual a -> Dual a Source #

spanMaybe :: s -> (s -> Dual a -> Maybe s) -> Dual a -> (Dual a, Dual a, s) Source #

spanMaybe' :: s -> (s -> Dual a -> Maybe s) -> Dual a -> (Dual a, Dual a, s) Source #

splitAt :: Int -> Dual a -> (Dual a, Dual a) Source #

drop :: Int -> Dual a -> Dual a Source #

take :: Int -> Dual a -> Dual a Source #

reverse :: Dual a -> Dual a Source #

(Integral a, Eq a) => FactorialMonoid (Sum a) Source # 
Instance details

Defined in Data.Monoid.Factorial

Methods

factors :: Sum a -> [Sum a] Source #

primePrefix :: Sum a -> Sum a Source #

primeSuffix :: Sum a -> Sum a Source #

splitPrimePrefix :: Sum a -> Maybe (Sum a, Sum a) Source #

splitPrimeSuffix :: Sum a -> Maybe (Sum a, Sum a) Source #

inits :: Sum a -> [Sum a] Source #

tails :: Sum a -> [Sum a] Source #

foldl :: (a0 -> Sum a -> a0) -> a0 -> Sum a -> a0 Source #

foldl' :: (a0 -> Sum a -> a0) -> a0 -> Sum a -> a0 Source #

foldr :: (Sum a -> a0 -> a0) -> a0 -> Sum a -> a0 Source #

length :: Sum a -> Int Source #

foldMap :: Monoid n => (Sum a -> n) -> Sum a -> n Source #

span :: (Sum a -> Bool) -> Sum a -> (Sum a, Sum a) Source #

break :: (Sum a -> Bool) -> Sum a -> (Sum a, Sum a) Source #

split :: (Sum a -> Bool) -> Sum a -> [Sum a] Source #

takeWhile :: (Sum a -> Bool) -> Sum a -> Sum a Source #

dropWhile :: (Sum a -> Bool) -> Sum a -> Sum a Source #

spanMaybe :: s -> (s -> Sum a -> Maybe s) -> Sum a -> (Sum a, Sum a, s) Source #

spanMaybe' :: s -> (s -> Sum a -> Maybe s) -> Sum a -> (Sum a, Sum a, s) Source #

splitAt :: Int -> Sum a -> (Sum a, Sum a) Source #

drop :: Int -> Sum a -> Sum a Source #

take :: Int -> Sum a -> Sum a Source #

reverse :: Sum a -> Sum a Source #

Integral a => FactorialMonoid (Product a) Source # 
Instance details

Defined in Data.Monoid.Factorial

Methods

factors :: Product a -> [Product a] Source #

primePrefix :: Product a -> Product a Source #

primeSuffix :: Product a -> Product a Source #

splitPrimePrefix :: Product a -> Maybe (Product a, Product a) Source #

splitPrimeSuffix :: Product a -> Maybe (Product a, Product a) Source #

inits :: Product a -> [Product a] Source #

tails :: Product a -> [Product a] Source #

foldl :: (a0 -> Product a -> a0) -> a0 -> Product a -> a0 Source #

foldl' :: (a0 -> Product a -> a0) -> a0 -> Product a -> a0 Source #

foldr :: (Product a -> a0 -> a0) -> a0 -> Product a -> a0 Source #

length :: Product a -> Int Source #

foldMap :: Monoid n => (Product a -> n) -> Product a -> n Source #

span :: (Product a -> Bool) -> Product a -> (Product a, Product a) Source #

break :: (Product a -> Bool) -> Product a -> (Product a, Product a) Source #

split :: (Product a -> Bool) -> Product a -> [Product a] Source #

takeWhile :: (Product a -> Bool) -> Product a -> Product a Source #

dropWhile :: (Product a -> Bool) -> Product a -> Product a Source #

spanMaybe :: s -> (s -> Product a -> Maybe s) -> Product a -> (Product a, Product a, s) Source #

spanMaybe' :: s -> (s -> Product a -> Maybe s) -> Product a -> (Product a, Product a, s) Source #

splitAt :: Int -> Product a -> (Product a, Product a) Source #

drop :: Int -> Product a -> Product a Source #

take :: Int -> Product a -> Product a Source #

reverse :: Product a -> Product a Source #

FactorialMonoid (IntMap a) Source # 
Instance details

Defined in Data.Monoid.Factorial

Methods

factors :: IntMap a -> [IntMap a] Source #

primePrefix :: IntMap a -> IntMap a Source #

primeSuffix :: IntMap a -> IntMap a Source #

splitPrimePrefix :: IntMap a -> Maybe (IntMap a, IntMap a) Source #

splitPrimeSuffix :: IntMap a -> Maybe (IntMap a, IntMap a) Source #

inits :: IntMap a -> [IntMap a] Source #

tails :: IntMap a -> [IntMap a] Source #

foldl :: (a0 -> IntMap a -> a0) -> a0 -> IntMap a -> a0 Source #

foldl' :: (a0 -> IntMap a -> a0) -> a0 -> IntMap a -> a0 Source #

foldr :: (IntMap a -> a0 -> a0) -> a0 -> IntMap a -> a0 Source #

length :: IntMap a -> Int Source #

foldMap :: Monoid n => (IntMap a -> n) -> IntMap a -> n Source #

span :: (IntMap a -> Bool) -> IntMap a -> (IntMap a, IntMap a) Source #

break :: (IntMap a -> Bool) -> IntMap a -> (IntMap a, IntMap a) Source #

split :: (IntMap a -> Bool) -> IntMap a -> [IntMap a] Source #

takeWhile :: (IntMap a -> Bool) -> IntMap a -> IntMap a Source #

dropWhile :: (IntMap a -> Bool) -> IntMap a -> IntMap a Source #

spanMaybe :: s -> (s -> IntMap a -> Maybe s) -> IntMap a -> (IntMap a, IntMap a, s) Source #

spanMaybe' :: s -> (s -> IntMap a -> Maybe s) -> IntMap a -> (IntMap a, IntMap a, s) Source #

splitAt :: Int -> IntMap a -> (IntMap a, IntMap a) Source #

drop :: Int -> IntMap a -> IntMap a Source #

take :: Int -> IntMap a -> IntMap a Source #

reverse :: IntMap a -> IntMap a Source #

FactorialMonoid (Seq a) Source # 
Instance details

Defined in Data.Monoid.Factorial

Methods

factors :: Seq a -> [Seq a] Source #

primePrefix :: Seq a -> Seq a Source #

primeSuffix :: Seq a -> Seq a Source #

splitPrimePrefix :: Seq a -> Maybe (Seq a, Seq a) Source #

splitPrimeSuffix :: Seq a -> Maybe (Seq a, Seq a) Source #

inits :: Seq a -> [Seq a] Source #

tails :: Seq a -> [Seq a] Source #

foldl :: (a0 -> Seq a -> a0) -> a0 -> Seq a -> a0 Source #

foldl' :: (a0 -> Seq a -> a0) -> a0 -> Seq a -> a0 Source #

foldr :: (Seq a -> a0 -> a0) -> a0 -> Seq a -> a0 Source #

length :: Seq a -> Int Source #

foldMap :: Monoid n => (Seq a -> n) -> Seq a -> n Source #

span :: (Seq a -> Bool) -> Seq a -> (Seq a, Seq a) Source #

break :: (Seq a -> Bool) -> Seq a -> (Seq a, Seq a) Source #

split :: (Seq a -> Bool) -> Seq a -> [Seq a] Source #

takeWhile :: (Seq a -> Bool) -> Seq a -> Seq a Source #

dropWhile :: (Seq a -> Bool) -> Seq a -> Seq a Source #

spanMaybe :: s -> (s -> Seq a -> Maybe s) -> Seq a -> (Seq a, Seq a, s) Source #

spanMaybe' :: s -> (s -> Seq a -> Maybe s) -> Seq a -> (Seq a, Seq a, s) Source #

splitAt :: Int -> Seq a -> (Seq a, Seq a) Source #

drop :: Int -> Seq a -> Seq a Source #

take :: Int -> Seq a -> Seq a Source #

reverse :: Seq a -> Seq a Source #

Ord a => FactorialMonoid (Set a) Source # 
Instance details

Defined in Data.Monoid.Factorial

Methods

factors :: Set a -> [Set a] Source #

primePrefix :: Set a -> Set a Source #

primeSuffix :: Set a -> Set a Source #

splitPrimePrefix :: Set a -> Maybe (Set a, Set a) Source #

splitPrimeSuffix :: Set a -> Maybe (Set a, Set a) Source #

inits :: Set a -> [Set a] Source #

tails :: Set a -> [Set a] Source #

foldl :: (a0 -> Set a -> a0) -> a0 -> Set a -> a0 Source #

foldl' :: (a0 -> Set a -> a0) -> a0 -> Set a -> a0 Source #

foldr :: (Set a -> a0 -> a0) -> a0 -> Set a -> a0 Source #

length :: Set a -> Int Source #

foldMap :: Monoid n => (Set a -> n) -> Set a -> n Source #

span :: (Set a -> Bool) -> Set a -> (Set a, Set a) Source #

break :: (Set a -> Bool) -> Set a -> (Set a, Set a) Source #

split :: (Set a -> Bool) -> Set a -> [Set a] Source #

takeWhile :: (Set a -> Bool) -> Set a -> Set a Source #

dropWhile :: (Set a -> Bool) -> Set a -> Set a Source #

spanMaybe :: s -> (s -> Set a -> Maybe s) -> Set a -> (Set a, Set a, s) Source #

spanMaybe' :: s -> (s -> Set a -> Maybe s) -> Set a -> (Set a, Set a, s) Source #

splitAt :: Int -> Set a -> (Set a, Set a) Source #

drop :: Int -> Set a -> Set a Source #

take :: Int -> Set a -> Set a Source #

reverse :: Set a -> Set a Source #

FactorialMonoid (Vector a) Source # 
Instance details

Defined in Data.Monoid.Factorial

Methods

factors :: Vector a -> [Vector a] Source #

primePrefix :: Vector a -> Vector a Source #

primeSuffix :: Vector a -> Vector a Source #

splitPrimePrefix :: Vector a -> Maybe (Vector a, Vector a) Source #

splitPrimeSuffix :: Vector a -> Maybe (Vector a, Vector a) Source #

inits :: Vector a -> [Vector a] Source #

tails :: Vector a -> [Vector a] Source #

foldl :: (a0 -> Vector a -> a0) -> a0 -> Vector a -> a0 Source #

foldl' :: (a0 -> Vector a -> a0) -> a0 -> Vector a -> a0 Source #

foldr :: (Vector a -> a0 -> a0) -> a0 -> Vector a -> a0 Source #

length :: Vector a -> Int Source #

foldMap :: Monoid n => (Vector a -> n) -> Vector a -> n Source #

span :: (Vector a -> Bool) -> Vector a -> (Vector a, Vector a) Source #

break :: (Vector a -> Bool) -> Vector a -> (Vector a, Vector a) Source #

split :: (Vector a -> Bool) -> Vector a -> [Vector a] Source #

takeWhile :: (Vector a -> Bool) -> Vector a -> Vector a Source #

dropWhile :: (Vector a -> Bool) -> Vector a -> Vector a Source #

spanMaybe :: s -> (s -> Vector a -> Maybe s) -> Vector a -> (Vector a, Vector a, s) Source #

spanMaybe' :: s -> (s -> Vector a -> Maybe s) -> Vector a -> (Vector a, Vector a, s) Source #

splitAt :: Int -> Vector a -> (Vector a, Vector a) Source #

drop :: Int -> Vector a -> Vector a Source #

take :: Int -> Vector a -> Vector a Source #

reverse :: Vector a -> Vector a Source #

(StableFactorialMonoid m, TextualMonoid m) => FactorialMonoid (LinePositioned m) Source # 
Instance details

Defined in Data.Monoid.Instances.Positioned

Methods

factors :: LinePositioned m -> [LinePositioned m] Source #

primePrefix :: LinePositioned m -> LinePositioned m Source #

primeSuffix :: LinePositioned m -> LinePositioned m Source #

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

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

inits :: LinePositioned m -> [LinePositioned m] Source #

tails :: LinePositioned m -> [LinePositioned m] Source #

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

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

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

length :: LinePositioned m -> Int Source #

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

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

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

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

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

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

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

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

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

drop :: Int -> LinePositioned m -> LinePositioned m Source #

take :: Int -> LinePositioned m -> LinePositioned m Source #

reverse :: LinePositioned m -> LinePositioned m Source #

StableFactorialMonoid m => FactorialMonoid (OffsetPositioned m) Source # 
Instance details

Defined in Data.Monoid.Instances.Positioned

Methods

factors :: OffsetPositioned m -> [OffsetPositioned m] Source #

primePrefix :: OffsetPositioned m -> OffsetPositioned m Source #

primeSuffix :: OffsetPositioned m -> OffsetPositioned m Source #

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

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

inits :: OffsetPositioned m -> [OffsetPositioned m] Source #

tails :: OffsetPositioned m -> [OffsetPositioned m] Source #

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

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

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

length :: OffsetPositioned m -> Int Source #

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

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

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

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

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

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

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

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

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

drop :: Int -> OffsetPositioned m -> OffsetPositioned m Source #

take :: Int -> OffsetPositioned m -> OffsetPositioned m Source #

reverse :: OffsetPositioned m -> OffsetPositioned m Source #

StableFactorialMonoid a => FactorialMonoid (Measured a) Source # 
Instance details

Defined in Data.Monoid.Instances.Measured

Methods

factors :: Measured a -> [Measured a] Source #

primePrefix :: Measured a -> Measured a Source #

primeSuffix :: Measured a -> Measured a Source #

splitPrimePrefix :: Measured a -> Maybe (Measured a, Measured a) Source #

splitPrimeSuffix :: Measured a -> Maybe (Measured a, Measured a) Source #

inits :: Measured a -> [Measured a] Source #

tails :: Measured a -> [Measured a] Source #

foldl :: (a0 -> Measured a -> a0) -> a0 -> Measured a -> a0 Source #

foldl' :: (a0 -> Measured a -> a0) -> a0 -> Measured a -> a0 Source #

foldr :: (Measured a -> a0 -> a0) -> a0 -> Measured a -> a0 Source #

length :: Measured a -> Int Source #

foldMap :: Monoid n => (Measured a -> n) -> Measured a -> n Source #

span :: (Measured a -> Bool) -> Measured a -> (Measured a, Measured a) Source #

break :: (Measured a -> Bool) -> Measured a -> (Measured a, Measured a) Source #

split :: (Measured a -> Bool) -> Measured a -> [Measured a] Source #

takeWhile :: (Measured a -> Bool) -> Measured a -> Measured a Source #

dropWhile :: (Measured a -> Bool) -> Measured a -> Measured a Source #

spanMaybe :: s -> (s -> Measured a -> Maybe s) -> Measured a -> (Measured a, Measured a, s) Source #

spanMaybe' :: s -> (s -> Measured a -> Maybe s) -> Measured a -> (Measured a, Measured a, s) Source #

splitAt :: Int -> Measured a -> (Measured a, Measured a) Source #

drop :: Int -> Measured a -> Measured a Source #

take :: Int -> Measured a -> Measured a Source #

reverse :: Measured a -> Measured a Source #

(FactorialMonoid a, PositiveMonoid a) => FactorialMonoid (Concat a) Source # 
Instance details

Defined in Data.Monoid.Instances.Concat

Methods

factors :: Concat a -> [Concat a] Source #

primePrefix :: Concat a -> Concat a Source #

primeSuffix :: Concat a -> Concat a Source #

splitPrimePrefix :: Concat a -> Maybe (Concat a, Concat a) Source #

splitPrimeSuffix :: Concat a -> Maybe (Concat a, Concat a) Source #

inits :: Concat a -> [Concat a] Source #

tails :: Concat a -> [Concat a] Source #

foldl :: (a0 -> Concat a -> a0) -> a0 -> Concat a -> a0 Source #

foldl' :: (a0 -> Concat a -> a0) -> a0 -> Concat a -> a0 Source #

foldr :: (Concat a -> a0 -> a0) -> a0 -> Concat a -> a0 Source #

length :: Concat a -> Int Source #

foldMap :: Monoid n => (Concat a -> n) -> Concat a -> n Source #

span :: (Concat a -> Bool) -> Concat a -> (Concat a, Concat a) Source #

break :: (Concat a -> Bool) -> Concat a -> (Concat a, Concat a) Source #

split :: (Concat a -> Bool) -> Concat a -> [Concat a] Source #

takeWhile :: (Concat a -> Bool) -> Concat a -> Concat a Source #

dropWhile :: (Concat a -> Bool) -> Concat a -> Concat a Source #

spanMaybe :: s -> (s -> Concat a -> Maybe s) -> Concat a -> (Concat a, Concat a, s) Source #

spanMaybe' :: s -> (s -> Concat a -> Maybe s) -> Concat a -> (Concat a, Concat a, s) Source #

splitAt :: Int -> Concat a -> (Concat a, Concat a) Source #

drop :: Int -> Concat a -> Concat a Source #

take :: Int -> Concat a -> Concat a Source #

reverse :: Concat a -> Concat a Source #

(FactorialMonoid a, FactorialMonoid b) => FactorialMonoid (a, b) Source # 
Instance details

Defined in Data.Monoid.Factorial

Methods

factors :: (a, b) -> [(a, b)] Source #

primePrefix :: (a, b) -> (a, b) Source #

primeSuffix :: (a, b) -> (a, b) Source #

splitPrimePrefix :: (a, b) -> Maybe ((a, b), (a, b)) Source #

splitPrimeSuffix :: (a, b) -> Maybe ((a, b), (a, b)) Source #

inits :: (a, b) -> [(a, b)] Source #

tails :: (a, b) -> [(a, b)] Source #

foldl :: (a0 -> (a, b) -> a0) -> a0 -> (a, b) -> a0 Source #

foldl' :: (a0 -> (a, b) -> a0) -> a0 -> (a, b) -> a0 Source #

foldr :: ((a, b) -> a0 -> a0) -> a0 -> (a, b) -> a0 Source #

length :: (a, b) -> Int Source #

foldMap :: Monoid n => ((a, b) -> n) -> (a, b) -> n Source #

span :: ((a, b) -> Bool) -> (a, b) -> ((a, b), (a, b)) Source #

break :: ((a, b) -> Bool) -> (a, b) -> ((a, b), (a, b)) Source #

split :: ((a, b) -> Bool) -> (a, b) -> [(a, b)] Source #

takeWhile :: ((a, b) -> Bool) -> (a, b) -> (a, b) Source #

dropWhile :: ((a, b) -> Bool) -> (a, b) -> (a, b) Source #

spanMaybe :: s -> (s -> (a, b) -> Maybe s) -> (a, b) -> ((a, b), (a, b), s) Source #

spanMaybe' :: s -> (s -> (a, b) -> Maybe s) -> (a, b) -> ((a, b), (a, b), s) Source #

splitAt :: Int -> (a, b) -> ((a, b), (a, b)) Source #

drop :: Int -> (a, b) -> (a, b) Source #

take :: Int -> (a, b) -> (a, b) Source #

reverse :: (a, b) -> (a, b) Source #

Ord k => FactorialMonoid (Map k v) Source # 
Instance details

Defined in Data.Monoid.Factorial

Methods

factors :: Map k v -> [Map k v] Source #

primePrefix :: Map k v -> Map k v Source #

primeSuffix :: Map k v -> Map k v Source #

splitPrimePrefix :: Map k v -> Maybe (Map k v, Map k v) Source #

splitPrimeSuffix :: Map k v -> Maybe (Map k v, Map k v) Source #

inits :: Map k v -> [Map k v] Source #

tails :: Map k v -> [Map k v] Source #

foldl :: (a -> Map k v -> a) -> a -> Map k v -> a Source #

foldl' :: (a -> Map k v -> a) -> a -> Map k v -> a Source #

foldr :: (Map k v -> a -> a) -> a -> Map k v -> a Source #

length :: Map k v -> Int Source #

foldMap :: Monoid n => (Map k v -> n) -> Map k v -> n Source #

span :: (Map k v -> Bool) -> Map k v -> (Map k v, Map k v) Source #

break :: (Map k v -> Bool) -> Map k v -> (Map k v, Map k v) Source #

split :: (Map k v -> Bool) -> Map k v -> [Map k v] Source #

takeWhile :: (Map k v -> Bool) -> Map k v -> Map k v Source #

dropWhile :: (Map k v -> Bool) -> Map k v -> Map k v Source #

spanMaybe :: s -> (s -> Map k v -> Maybe s) -> Map k v -> (Map k v, Map k v, s) Source #

spanMaybe' :: s -> (s -> Map k v -> Maybe s) -> Map k v -> (Map k v, Map k v, s) Source #

splitAt :: Int -> Map k v -> (Map k v, Map k v) Source #

drop :: Int -> Map k v -> Map k v Source #

take :: Int -> Map k v -> Map k v Source #

reverse :: Map k v -> Map k v Source #

(FactorialMonoid a, FactorialMonoid b) => FactorialMonoid (Stateful a b) Source # 
Instance details

Defined in Data.Monoid.Instances.Stateful

Methods

factors :: Stateful a b -> [Stateful a b] Source #

primePrefix :: Stateful a b -> Stateful a b Source #

primeSuffix :: Stateful a b -> Stateful a b Source #

splitPrimePrefix :: Stateful a b -> Maybe (Stateful a b, Stateful a b) Source #

splitPrimeSuffix :: Stateful a b -> Maybe (Stateful a b, Stateful a b) Source #

inits :: Stateful a b -> [Stateful a b] Source #

tails :: Stateful a b -> [Stateful a b] Source #

foldl :: (a0 -> Stateful a b -> a0) -> a0 -> Stateful a b -> a0 Source #

foldl' :: (a0 -> Stateful a b -> a0) -> a0 -> Stateful a b -> a0 Source #

foldr :: (Stateful a b -> a0 -> a0) -> a0 -> Stateful a b -> a0 Source #

length :: Stateful a b -> Int Source #

foldMap :: Monoid n => (Stateful a b -> n) -> Stateful a b -> n Source #

span :: (Stateful a b -> Bool) -> Stateful a b -> (Stateful a b, Stateful a b) Source #

break :: (Stateful a b -> Bool) -> Stateful a b -> (Stateful a b, Stateful a b) Source #

split :: (Stateful a b -> Bool) -> Stateful a b -> [Stateful a b] Source #

takeWhile :: (Stateful a b -> Bool) -> Stateful a b -> Stateful a b Source #

dropWhile :: (Stateful a b -> Bool) -> Stateful a b -> Stateful a b Source #

spanMaybe :: s -> (s -> Stateful a b -> Maybe s) -> Stateful a b -> (Stateful a b, Stateful a b, s) Source #

spanMaybe' :: s -> (s -> Stateful a b -> Maybe s) -> Stateful a b -> (Stateful a b, Stateful a b, s) Source #

splitAt :: Int -> Stateful a b -> (Stateful a b, Stateful a b) Source #

drop :: Int -> Stateful a b -> Stateful a b Source #

take :: Int -> Stateful a b -> Stateful a b Source #

reverse :: Stateful a b -> Stateful a b Source #

(FactorialMonoid a, FactorialMonoid b, FactorialMonoid c) => FactorialMonoid (a, b, c) Source # 
Instance details

Defined in Data.Monoid.Factorial

Methods

factors :: (a, b, c) -> [(a, b, c)] Source #

primePrefix :: (a, b, c) -> (a, b, c) Source #

primeSuffix :: (a, b, c) -> (a, b, c) Source #

splitPrimePrefix :: (a, b, c) -> Maybe ((a, b, c), (a, b, c)) Source #

splitPrimeSuffix :: (a, b, c) -> Maybe ((a, b, c), (a, b, c)) Source #

inits :: (a, b, c) -> [(a, b, c)] Source #

tails :: (a, b, c) -> [(a, b, c)] Source #

foldl :: (a0 -> (a, b, c) -> a0) -> a0 -> (a, b, c) -> a0 Source #

foldl' :: (a0 -> (a, b, c) -> a0) -> a0 -> (a, b, c) -> a0 Source #

foldr :: ((a, b, c) -> a0 -> a0) -> a0 -> (a, b, c) -> a0 Source #

length :: (a, b, c) -> Int Source #

foldMap :: Monoid n => ((a, b, c) -> n) -> (a, b, c) -> n Source #

span :: ((a, b, c) -> Bool) -> (a, b, c) -> ((a, b, c), (a, b, c)) Source #

break :: ((a, b, c) -> Bool) -> (a, b, c) -> ((a, b, c), (a, b, c)) Source #

split :: ((a, b, c) -> Bool) -> (a, b, c) -> [(a, b, c)] Source #

takeWhile :: ((a, b, c) -> Bool) -> (a, b, c) -> (a, b, c) Source #

dropWhile :: ((a, b, c) -> Bool) -> (a, b, c) -> (a, b, c) Source #

spanMaybe :: s -> (s -> (a, b, c) -> Maybe s) -> (a, b, c) -> ((a, b, c), (a, b, c), s) Source #

spanMaybe' :: s -> (s -> (a, b, c) -> Maybe s) -> (a, b, c) -> ((a, b, c), (a, b, c), s) Source #

splitAt :: Int -> (a, b, c) -> ((a, b, c), (a, b, c)) Source #

drop :: Int -> (a, b, c) -> (a, b, c) Source #

take :: Int -> (a, b, c) -> (a, b, c) Source #

reverse :: (a, b, c) -> (a, b, c) Source #

(FactorialMonoid a, FactorialMonoid b, FactorialMonoid c, FactorialMonoid d) => FactorialMonoid (a, b, c, d) Source # 
Instance details

Defined in Data.Monoid.Factorial

Methods

factors :: (a, b, c, d) -> [(a, b, c, d)] Source #

primePrefix :: (a, b, c, d) -> (a, b, c, d) Source #

primeSuffix :: (a, b, c, d) -> (a, b, c, d) Source #

splitPrimePrefix :: (a, b, c, d) -> Maybe ((a, b, c, d), (a, b, c, d)) Source #

splitPrimeSuffix :: (a, b, c, d) -> Maybe ((a, b, c, d), (a, b, c, d)) Source #

inits :: (a, b, c, d) -> [(a, b, c, d)] Source #

tails :: (a, b, c, d) -> [(a, b, c, d)] Source #

foldl :: (a0 -> (a, b, c, d) -> a0) -> a0 -> (a, b, c, d) -> a0 Source #

foldl' :: (a0 -> (a, b, c, d) -> a0) -> a0 -> (a, b, c, d) -> a0 Source #

foldr :: ((a, b, c, d) -> a0 -> a0) -> a0 -> (a, b, c, d) -> a0 Source #

length :: (a, b, c, d) -> Int Source #

foldMap :: Monoid n => ((a, b, c, d) -> n) -> (a, b, c, d) -> n Source #

span :: ((a, b, c, d) -> Bool) -> (a, b, c, d) -> ((a, b, c, d), (a, b, c, d)) Source #

break :: ((a, b, c, d) -> Bool) -> (a, b, c, d) -> ((a, b, c, d), (a, b, c, d)) Source #

split :: ((a, b, c, d) -> Bool) -> (a, b, c, d) -> [(a, b, c, d)] Source #

takeWhile :: ((a, b, c, d) -> Bool) -> (a, b, c, d) -> (a, b, c, d) Source #

dropWhile :: ((a, b, c, d) -> Bool) -> (a, b, c, d) -> (a, b, c, d) Source #

spanMaybe :: s -> (s -> (a, b, c, d) -> Maybe s) -> (a, b, c, d) -> ((a, b, c, d), (a, b, c, d), s) Source #

spanMaybe' :: s -> (s -> (a, b, c, d) -> Maybe s) -> (a, b, c, d) -> ((a, b, c, d), (a, b, c, d), s) Source #

splitAt :: Int -> (a, b, c, d) -> ((a, b, c, d), (a, b, c, d)) Source #

drop :: Int -> (a, b, c, d) -> (a, b, c, d) Source #

take :: Int -> (a, b, c, d) -> (a, b, c, d) Source #

reverse :: (a, b, c, d) -> (a, b, c, d) Source #

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
StableFactorialMonoid () Source # 
Instance details

Defined in Data.Monoid.Factorial

StableFactorialMonoid ByteString Source # 
Instance details

Defined in Data.Monoid.Factorial

StableFactorialMonoid ByteString Source # 
Instance details

Defined in Data.Monoid.Factorial

StableFactorialMonoid Text Source # 
Instance details

Defined in Data.Monoid.Factorial

StableFactorialMonoid Text Source # 
Instance details

Defined in Data.Monoid.Factorial

StableFactorialMonoid [x] Source # 
Instance details

Defined in Data.Monoid.Factorial

StableFactorialMonoid a => StableFactorialMonoid (Dual a) Source # 
Instance details

Defined in Data.Monoid.Factorial

StableFactorialMonoid (Seq a) Source # 
Instance details

Defined in Data.Monoid.Factorial

StableFactorialMonoid (Vector a) Source # 
Instance details

Defined in Data.Monoid.Factorial

(StableFactorialMonoid m, TextualMonoid m) => StableFactorialMonoid (LinePositioned m) Source # 
Instance details

Defined in Data.Monoid.Instances.Positioned

StableFactorialMonoid m => StableFactorialMonoid (OffsetPositioned m) Source # 
Instance details

Defined in Data.Monoid.Instances.Positioned

StableFactorialMonoid a => StableFactorialMonoid (Measured a) Source # 
Instance details

Defined in Data.Monoid.Instances.Measured

(FactorialMonoid a, PositiveMonoid a) => StableFactorialMonoid (Concat a) Source # 
Instance details

Defined in Data.Monoid.Instances.Concat

(StableFactorialMonoid a, StableFactorialMonoid b) => StableFactorialMonoid (Stateful a b) Source # 
Instance details

Defined in Data.Monoid.Instances.Stateful

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.