monoid-subclasses-0.3: Subclasses of Monoid

Safe HaskellNone

Data.Monoid.Textual

Description

This module defines the TextualMonoid class and its most important instances for String and Text.

Synopsis

Documentation

class (IsString t, LeftReductiveMonoid t, LeftGCDMonoid t, FactorialMonoid t) => TextualMonoid t whereSource

The TextualMonoid class is an extension of FactorialMonoid specialized for monoids that can contain characters. Its methods are generally equivalent to their namesake functions from Data.List and Data.Text, and they satisfy the following laws:

 splitCharacterPrefix (singleton c <> t) == Just (c, t)
 splitCharacterPrefix . primePrefix == fmap (\(c, t)-> (c, mempty)) . splitCharacterPrefix

 map f . fromString == fromString . List.map f
 concatMap (fromString . f) . fromString == fromString . List.concatMap f

 foldl  ft fc a . fromString == List.foldl  fc a
 foldr  ft fc a . fromString == List.foldr  fc a
 foldl' ft fc a . fromString == List.foldl' fc a

 scanl f c . fromString == fromString . List.scanl f c
 scanr f c . fromString == fromString . List.scanr f c
 mapAccumL f a . fromString == fmap fromString . List.mapAccumL f a
 mapAccumL f a . fromString == fmap fromString . List.mapAccumL f a

 takeWhile pt pc . fromString == fromString . takeWhile pc
 dropWhile pt pc . fromString == fromString . dropWhile pc

 mconcat . intersperse (singleton c) . split (== c) == id
 find p . fromString == List.find p

A TextualMonoid may contain non-character data insterspersed between its characters. Every class method that returns a modified TextualMonoid instance generally preserves this non-character data. All of the following expressions are identities:

 map id
 concatMap singleton
 foldl  (<>) (\a c-> a <> singleton c) mempty
 foldr  (<>) ((<>) . singleton) mempty
 foldl' (<>) (\a c-> a <> singleton c) mempty
 scanl1 (const id)
 scanr1 const
 uncurry (mapAccumL (,))
 uncurry (mapAccumR (,))
 takeWhile (const True) (const True)
 dropWhile (const False) (const False)

A minimal instance definition must implement splitCharacterPrefix.

Methods

fromText :: Text -> tSource

Contructs a new data type instance Like fromString, but from a Text input instead of String.

 fromText == fromString . Text.unpack

singleton :: Char -> tSource

Creates a prime monoid containing a single character.

 singleton c == fromString [c]

splitCharacterPrefix :: t -> Maybe (Char, t)Source

Specialized version of splitPrimePrefix. Every prime factor of a Textual monoid must consist of a single character or no character at all.

characterPrefix :: t -> Maybe CharSource

Extracts a single character that prefixes the monoid, if the monoid begins with a character. Otherwise returns Nothing.

 characterPrefix == fmap fst . splitCharacterPrefix

map :: (Char -> Char) -> t -> tSource

Equivalent to map from Data.List with a Char -> Char function. Preserves all non-character data.

 map f == concatMap (singleton . f)

concatMap :: (Char -> t) -> t -> tSource

Equivalent to concatMap from Data.List with a Char -> String function. Preserves all non-character data.

any :: (Char -> Bool) -> t -> BoolSource

Equivalent to any from Data.List. Ignores all non-character data.

all :: (Char -> Bool) -> t -> BoolSource

Equivalent to all from Data.List. Ignores all non-character data.

foldl :: (a -> t -> a) -> (a -> Char -> a) -> a -> t -> aSource

The first argument folds over the non-character prime factors, the second over characters. Otherwise equivalent to foldl from Data.List.

foldl' :: (a -> t -> a) -> (a -> Char -> a) -> a -> t -> aSource

Strict version of foldl.

foldr :: (t -> a -> a) -> (Char -> a -> a) -> a -> t -> aSource

The first argument folds over the non-character prime factors, the second over characters. Otherwise equivalent to foldr from Data.List.

scanl :: (Char -> Char -> Char) -> Char -> t -> tSource

Equivalent to scanl from Data.List when applied to a String, but preserves all non-character data.

scanl1 :: (Char -> Char -> Char) -> t -> tSource

Equivalent to scanl1 from Data.List when applied to a String, but preserves all non-character data.

 scanl f c == scanl1 f . (singleton c <>)

scanr :: (Char -> Char -> Char) -> Char -> t -> tSource

Equivalent to scanr from Data.List when applied to a String, but preserves all non-character data.

scanr1 :: (Char -> Char -> Char) -> t -> tSource

Equivalent to scanr1 from Data.List when applied to a String, but preserves all non-character data.

 scanr f c == scanr1 f . (<> singleton c)

mapAccumL :: (a -> Char -> (a, Char)) -> a -> t -> (a, t)Source

Equivalent to mapAccumL from Data.List when applied to a String, but preserves all non-character data.

mapAccumR :: (a -> Char -> (a, Char)) -> a -> t -> (a, t)Source

Equivalent to mapAccumR from Data.List when applied to a String, but preserves all non-character data.

takeWhile :: (t -> Bool) -> (Char -> Bool) -> t -> tSource

The first predicate tests the non-character data, the second one the characters. Otherwise equivalent to takeWhile from Data.List when applied to a String.

dropWhile :: (t -> Bool) -> (Char -> Bool) -> t -> tSource

The first predicate tests the non-character data, the second one the characters. Otherwise equivalent to dropWhile from Data.List when applied to a String.

break :: (t -> Bool) -> (Char -> Bool) -> t -> (t, t)Source

'break pt pc' is equivalent to |span (not . pt) (not . pc)|.

span :: (t -> Bool) -> (Char -> Bool) -> t -> (t, t)Source

'span pt pc t' is equivalent to |(takeWhile pt pc t, dropWhile pt pc t)|.

split :: (Char -> Bool) -> t -> [t]Source

Splits the monoid into components delimited by character separators satisfying the given predicate. The characters satisfying the predicate are not a part of the result.

 split p == Factorial.split (maybe False p . characterPrefix)

find :: (Char -> Bool) -> t -> Maybe CharSource

Like find from Data.List when applied to a String. Ignores non-character data.