monoid-subclasses-1.0: Subclasses of Monoid

Safe HaskellTrustworthy
LanguageHaskell2010

Data.Monoid.Factorial

Description

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

Synopsis

Documentation

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.

Minimal complete definition

Nothing

Methods

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.

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.

Instances
FactorialMonoid () Source # 
Instance details

Defined in Data.Monoid.Factorial

Methods

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

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

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

tails :: () -> [()] 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 #

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

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

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

inits :: Text -> [Text] Source #

tails :: Text -> [Text] 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 #

FactorialMonoid Text Source # 
Instance details

Defined in Data.Monoid.Factorial

Methods

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

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

inits :: Text -> [Text] Source #

tails :: Text -> [Text] 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 #

FactorialMonoid ByteStringUTF8 Source # 
Instance details

Defined in Data.Monoid.Instances.ByteString.UTF8

FactorialMonoid [x] Source # 
Instance details

Defined in Data.Monoid.Factorial

Methods

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

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

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

tails :: [x] -> [[x]] 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 #

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

Defined in Data.Monoid.Factorial

Methods

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 #

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 #

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

Defined in Data.Monoid.Factorial

Methods

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 #

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 #

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

Defined in Data.Monoid.Factorial

Methods

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 #

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 #

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

Defined in Data.Monoid.Factorial

Methods

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 #

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 #

FactorialMonoid (IntMap a) Source # 
Instance details

Defined in Data.Monoid.Factorial

Methods

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 #

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 #

FactorialMonoid (Seq a) Source # 
Instance details

Defined in Data.Monoid.Factorial

Methods

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 #

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 #

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

Defined in Data.Monoid.Factorial

Methods

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 #

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 #

FactorialMonoid (Vector a) Source # 
Instance details

Defined in Data.Monoid.Factorial

Methods

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 #

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 #

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

Defined in Data.Monoid.Instances.Positioned

(StableFactorial m, FactorialMonoid m) => FactorialMonoid (OffsetPositioned m) Source # 
Instance details

Defined in Data.Monoid.Instances.Positioned

(StableFactorial a, FactorialMonoid a) => FactorialMonoid (Measured a) Source # 
Instance details

Defined in Data.Monoid.Instances.Measured

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

Defined in Data.Monoid.Instances.Concat

Methods

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 #

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 #

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

Defined in Data.Monoid.Factorial

Methods

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 #

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 #

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

Defined in Data.Monoid.Factorial

Methods

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 #

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 #

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

Defined in Data.Monoid.Instances.Stateful

Methods

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 #

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 #

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

Defined in Data.Monoid.Factorial

Methods

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 #

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 #

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

Defined in Data.Monoid.Factorial

Methods

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 #

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 #

type StableFactorialMonoid m = (StableFactorial m, FactorialMonoid m, PositiveMonoid m) Source #

Deprecated: Use Data.Semigroup.Factorial.StableFactorial instead.