Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
This module defines the TextualMonoid
class and several of its instances.
- class (IsString t, LeftReductiveMonoid t, LeftGCDMonoid t, FactorialMonoid t) => TextualMonoid t where
- fromText :: Text -> t
- singleton :: Char -> t
- splitCharacterPrefix :: t -> Maybe (Char, t)
- characterPrefix :: t -> Maybe Char
- map :: (Char -> Char) -> t -> t
- concatMap :: (Char -> t) -> t -> t
- any :: (Char -> Bool) -> t -> Bool
- all :: (Char -> Bool) -> t -> Bool
- foldl :: (a -> t -> a) -> (a -> Char -> a) -> a -> t -> a
- foldl' :: (a -> t -> a) -> (a -> Char -> a) -> a -> t -> a
- foldr :: (t -> a -> a) -> (Char -> a -> a) -> a -> t -> a
- scanl :: (Char -> Char -> Char) -> Char -> t -> t
- scanl1 :: (Char -> Char -> Char) -> t -> t
- scanr :: (Char -> Char -> Char) -> Char -> t -> t
- scanr1 :: (Char -> Char -> Char) -> t -> t
- mapAccumL :: (a -> Char -> (a, Char)) -> a -> t -> (a, t)
- mapAccumR :: (a -> Char -> (a, Char)) -> a -> t -> (a, t)
- takeWhile :: (t -> Bool) -> (Char -> Bool) -> t -> t
- dropWhile :: (t -> Bool) -> (Char -> Bool) -> t -> t
- break :: (t -> Bool) -> (Char -> Bool) -> t -> (t, t)
- span :: (t -> Bool) -> (Char -> Bool) -> t -> (t, t)
- spanMaybe :: s -> (s -> t -> Maybe s) -> (s -> Char -> Maybe s) -> t -> (t, t, s)
- spanMaybe' :: s -> (s -> t -> Maybe s) -> (s -> Char -> Maybe s) -> t -> (t, t, s)
- split :: (Char -> Bool) -> t -> [t]
- find :: (Char -> Bool) -> t -> Maybe Char
- elem :: Char -> t -> Bool
- foldl_ :: (a -> Char -> a) -> a -> t -> a
- foldl_' :: (a -> Char -> a) -> a -> t -> a
- foldr_ :: (Char -> a -> a) -> a -> t -> a
- takeWhile_ :: Bool -> (Char -> Bool) -> t -> t
- dropWhile_ :: Bool -> (Char -> Bool) -> t -> t
- break_ :: Bool -> (Char -> Bool) -> t -> (t, t)
- span_ :: Bool -> (Char -> Bool) -> t -> (t, t)
- spanMaybe_ :: s -> (s -> Char -> Maybe s) -> t -> (t, t, s)
- spanMaybe_' :: s -> (s -> Char -> Maybe s) -> t -> (t, t, s)
Documentation
class (IsString t, LeftReductiveMonoid t, LeftGCDMonoid t, FactorialMonoid t) => TextualMonoid t where Source
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:
unfoldr splitCharacterPrefix . fromString == id 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 elem c . fromString == List.elem c
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. Methods like foldr
can
access both the non-character and character data and expect two arguments for the two purposes. For each of these
methods there is also a simplified version with underscore in name (like foldr_
) that ignores the 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
.
Contructs a new data type instance Like fromString
, but from a Text
input instead of String
.
fromText == fromString . Text.unpack
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 Char Source
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 -> t Source
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 -> t Source
Equivalent to concatMap
from Data.List with a Char -> String
function. Preserves all non-character
data.
any :: (Char -> Bool) -> t -> Bool Source
all :: (Char -> Bool) -> t -> Bool Source
foldl :: (a -> t -> a) -> (a -> Char -> a) -> a -> t -> a Source
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 -> a Source
Strict version of foldl
.
foldr :: (t -> a -> a) -> (Char -> a -> a) -> a -> t -> a Source
The first argument folds over the non-character prime factors, the second over characters. Otherwise equivalent to 'List.foldl\'' from Data.List.
scanl :: (Char -> Char -> Char) -> Char -> t -> t Source
scanl1 :: (Char -> Char -> Char) -> t -> t Source
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 -> t Source
scanr1 :: (Char -> Char -> Char) -> t -> t Source
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 -> t Source
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 -> t Source
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)|.
spanMaybe :: s -> (s -> t -> Maybe s) -> (s -> Char -> Maybe s) -> t -> (t, t, s) Source
spanMaybe' :: s -> (s -> t -> Maybe s) -> (s -> Char -> Maybe s) -> t -> (t, t, s) Source
Strict version of spanMaybe
.
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 Char Source
elem :: Char -> t -> Bool Source
foldl_ :: (a -> Char -> a) -> a -> t -> a Source
foldl_ = foldl const
foldl_' :: (a -> Char -> a) -> a -> t -> a Source
foldr_ :: (Char -> a -> a) -> a -> t -> a Source
takeWhile_ :: Bool -> (Char -> Bool) -> t -> t Source
takeWhile_ = takeWhile . const
dropWhile_ :: Bool -> (Char -> Bool) -> t -> t Source
dropWhile_ = dropWhile . const
break_ :: Bool -> (Char -> Bool) -> t -> (t, t) Source
break_ = break . const
span_ :: Bool -> (Char -> Bool) -> t -> (t, t) Source
span_ = span . const
spanMaybe_ :: s -> (s -> Char -> Maybe s) -> t -> (t, t, s) Source
spanMaybe_ s = spanMaybe s (const . Just)
spanMaybe_' :: s -> (s -> Char -> Maybe s) -> t -> (t, t, s) Source
TextualMonoid String | |
TextualMonoid Text | |
TextualMonoid Text | |
TextualMonoid ByteStringUTF8 | |
TextualMonoid (Seq Char) | |
TextualMonoid (Vector Char) | |
(Eq a, TextualMonoid a, StableFactorialMonoid a) => TextualMonoid (Concat a) | |
(Eq a, TextualMonoid a, StableFactorialMonoid a) => TextualMonoid (Measured a) | |
(StableFactorialMonoid m, TextualMonoid m) => TextualMonoid (LinePositioned m) | |
(StableFactorialMonoid m, TextualMonoid m) => TextualMonoid (OffsetPositioned m) | |
(LeftGCDMonoid a, FactorialMonoid a, TextualMonoid b) => TextualMonoid (Stateful a b) |