monoid-subclasses-1.2.3: Subclasses of Monoid
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Monoid.Textual

Description

This module defines the TextualMonoid class and several of its instances.

Synopsis

Documentation

class (IsString t, LeftReductive 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)
toString undefined . fromString
toText undefined . fromText

Minimal complete definition

splitCharacterPrefix

Methods

fromText :: Text -> t Source #

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

fromText == fromString . Text.unpack

singleton :: Char -> t Source #

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.

toString :: (t -> String) -> t -> String Source #

Returns the list of characters the monoid contains, once the argument function converts all its non-character factors into characters.

toText :: (t -> Text) -> t -> Text Source #

Converts the monoid into Text, given a function to convert the non-character factors into chunks of Text.

any :: (Char -> Bool) -> t -> Bool Source #

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

all :: (Char -> Bool) -> t -> Bool Source #

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

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 #

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

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 #

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

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 #

A stateful variant of span, threading the result of the test function as long as it returns Just.

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 #

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

elem :: Char -> t -> Bool Source #

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

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 #

Instances

Instances details
TextualMonoid ByteStringUTF8 Source # 
Instance details

Defined in Data.Monoid.Instances.ByteString.UTF8

Methods

fromText :: Text -> ByteStringUTF8 Source #

singleton :: Char -> ByteStringUTF8 Source #

splitCharacterPrefix :: ByteStringUTF8 -> Maybe (Char, ByteStringUTF8) Source #

characterPrefix :: ByteStringUTF8 -> Maybe Char Source #

map :: (Char -> Char) -> ByteStringUTF8 -> ByteStringUTF8 Source #

concatMap :: (Char -> ByteStringUTF8) -> ByteStringUTF8 -> ByteStringUTF8 Source #

toString :: (ByteStringUTF8 -> String) -> ByteStringUTF8 -> String Source #

toText :: (ByteStringUTF8 -> Text) -> ByteStringUTF8 -> Text Source #

any :: (Char -> Bool) -> ByteStringUTF8 -> Bool Source #

all :: (Char -> Bool) -> ByteStringUTF8 -> Bool Source #

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

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

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

scanl :: (Char -> Char -> Char) -> Char -> ByteStringUTF8 -> ByteStringUTF8 Source #

scanl1 :: (Char -> Char -> Char) -> ByteStringUTF8 -> ByteStringUTF8 Source #

scanr :: (Char -> Char -> Char) -> Char -> ByteStringUTF8 -> ByteStringUTF8 Source #

scanr1 :: (Char -> Char -> Char) -> ByteStringUTF8 -> ByteStringUTF8 Source #

mapAccumL :: (a -> Char -> (a, Char)) -> a -> ByteStringUTF8 -> (a, ByteStringUTF8) Source #

mapAccumR :: (a -> Char -> (a, Char)) -> a -> ByteStringUTF8 -> (a, ByteStringUTF8) Source #

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

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

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

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

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

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

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

find :: (Char -> Bool) -> ByteStringUTF8 -> Maybe Char Source #

elem :: Char -> ByteStringUTF8 -> Bool Source #

foldl_ :: (a -> Char -> a) -> a -> ByteStringUTF8 -> a Source #

foldl_' :: (a -> Char -> a) -> a -> ByteStringUTF8 -> a Source #

foldr_ :: (Char -> a -> a) -> a -> ByteStringUTF8 -> a Source #

takeWhile_ :: Bool -> (Char -> Bool) -> ByteStringUTF8 -> ByteStringUTF8 Source #

dropWhile_ :: Bool -> (Char -> Bool) -> ByteStringUTF8 -> ByteStringUTF8 Source #

break_ :: Bool -> (Char -> Bool) -> ByteStringUTF8 -> (ByteStringUTF8, ByteStringUTF8) Source #

span_ :: Bool -> (Char -> Bool) -> ByteStringUTF8 -> (ByteStringUTF8, ByteStringUTF8) Source #

spanMaybe_ :: s -> (s -> Char -> Maybe s) -> ByteStringUTF8 -> (ByteStringUTF8, ByteStringUTF8, s) Source #

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

TextualMonoid Text Source # 
Instance details

Defined in Data.Monoid.Textual

Methods

fromText :: Text -> Text Source #

singleton :: Char -> Text Source #

splitCharacterPrefix :: Text -> Maybe (Char, Text) Source #

characterPrefix :: Text -> Maybe Char Source #

map :: (Char -> Char) -> Text -> Text Source #

concatMap :: (Char -> Text) -> Text -> Text Source #

toString :: (Text -> String) -> Text -> String Source #

toText :: (Text -> Text) -> Text -> Text Source #

any :: (Char -> Bool) -> Text -> Bool Source #

all :: (Char -> Bool) -> Text -> Bool Source #

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

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

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

scanl :: (Char -> Char -> Char) -> Char -> Text -> Text Source #

scanl1 :: (Char -> Char -> Char) -> Text -> Text Source #

scanr :: (Char -> Char -> Char) -> Char -> Text -> Text Source #

scanr1 :: (Char -> Char -> Char) -> Text -> Text Source #

mapAccumL :: (a -> Char -> (a, Char)) -> a -> Text -> (a, Text) Source #

mapAccumR :: (a -> Char -> (a, Char)) -> a -> Text -> (a, Text) Source #

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

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

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

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

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

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

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

find :: (Char -> Bool) -> Text -> Maybe Char Source #

elem :: Char -> Text -> Bool Source #

foldl_ :: (a -> Char -> a) -> a -> Text -> a Source #

foldl_' :: (a -> Char -> a) -> a -> Text -> a Source #

foldr_ :: (Char -> a -> a) -> a -> Text -> a Source #

takeWhile_ :: Bool -> (Char -> Bool) -> Text -> Text Source #

dropWhile_ :: Bool -> (Char -> Bool) -> Text -> Text Source #

break_ :: Bool -> (Char -> Bool) -> Text -> (Text, Text) Source #

span_ :: Bool -> (Char -> Bool) -> Text -> (Text, Text) Source #

spanMaybe_ :: s -> (s -> Char -> Maybe s) -> Text -> (Text, Text, s) Source #

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

TextualMonoid Text Source # 
Instance details

Defined in Data.Monoid.Textual

Methods

fromText :: Text0 -> Text Source #

singleton :: Char -> Text Source #

splitCharacterPrefix :: Text -> Maybe (Char, Text) Source #

characterPrefix :: Text -> Maybe Char Source #

map :: (Char -> Char) -> Text -> Text Source #

concatMap :: (Char -> Text) -> Text -> Text Source #

toString :: (Text -> String) -> Text -> String Source #

toText :: (Text -> Text0) -> Text -> Text0 Source #

any :: (Char -> Bool) -> Text -> Bool Source #

all :: (Char -> Bool) -> Text -> Bool Source #

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

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

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

scanl :: (Char -> Char -> Char) -> Char -> Text -> Text Source #

scanl1 :: (Char -> Char -> Char) -> Text -> Text Source #

scanr :: (Char -> Char -> Char) -> Char -> Text -> Text Source #

scanr1 :: (Char -> Char -> Char) -> Text -> Text Source #

mapAccumL :: (a -> Char -> (a, Char)) -> a -> Text -> (a, Text) Source #

mapAccumR :: (a -> Char -> (a, Char)) -> a -> Text -> (a, Text) Source #

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

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

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

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

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

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

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

find :: (Char -> Bool) -> Text -> Maybe Char Source #

elem :: Char -> Text -> Bool Source #

foldl_ :: (a -> Char -> a) -> a -> Text -> a Source #

foldl_' :: (a -> Char -> a) -> a -> Text -> a Source #

foldr_ :: (Char -> a -> a) -> a -> Text -> a Source #

takeWhile_ :: Bool -> (Char -> Bool) -> Text -> Text Source #

dropWhile_ :: Bool -> (Char -> Bool) -> Text -> Text Source #

break_ :: Bool -> (Char -> Bool) -> Text -> (Text, Text) Source #

span_ :: Bool -> (Char -> Bool) -> Text -> (Text, Text) Source #

spanMaybe_ :: s -> (s -> Char -> Maybe s) -> Text -> (Text, Text, s) Source #

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

TextualMonoid String Source # 
Instance details

Defined in Data.Monoid.Textual

Methods

fromText :: Text -> String Source #

singleton :: Char -> String Source #

splitCharacterPrefix :: String -> Maybe (Char, String) Source #

characterPrefix :: String -> Maybe Char Source #

map :: (Char -> Char) -> String -> String Source #

concatMap :: (Char -> String) -> String -> String Source #

toString :: (String -> String) -> String -> String Source #

toText :: (String -> Text) -> String -> Text Source #

any :: (Char -> Bool) -> String -> Bool Source #

all :: (Char -> Bool) -> String -> Bool Source #

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

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

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

scanl :: (Char -> Char -> Char) -> Char -> String -> String Source #

scanl1 :: (Char -> Char -> Char) -> String -> String Source #

scanr :: (Char -> Char -> Char) -> Char -> String -> String Source #

scanr1 :: (Char -> Char -> Char) -> String -> String Source #

mapAccumL :: (a -> Char -> (a, Char)) -> a -> String -> (a, String) Source #

mapAccumR :: (a -> Char -> (a, Char)) -> a -> String -> (a, String) Source #

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

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

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

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

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

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

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

find :: (Char -> Bool) -> String -> Maybe Char Source #

elem :: Char -> String -> Bool Source #

foldl_ :: (a -> Char -> a) -> a -> String -> a Source #

foldl_' :: (a -> Char -> a) -> a -> String -> a Source #

foldr_ :: (Char -> a -> a) -> a -> String -> a Source #

takeWhile_ :: Bool -> (Char -> Bool) -> String -> String Source #

dropWhile_ :: Bool -> (Char -> Bool) -> String -> String Source #

break_ :: Bool -> (Char -> Bool) -> String -> (String, String) Source #

span_ :: Bool -> (Char -> Bool) -> String -> (String, String) Source #

spanMaybe_ :: s -> (s -> Char -> Maybe s) -> String -> (String, String, s) Source #

spanMaybe_' :: s -> (s -> Char -> Maybe s) -> String -> (String, String, s) Source #

TextualMonoid (Seq Char) Source # 
Instance details

Defined in Data.Monoid.Textual

Methods

fromText :: Text -> Seq Char Source #

singleton :: Char -> Seq Char Source #

splitCharacterPrefix :: Seq Char -> Maybe (Char, Seq Char) Source #

characterPrefix :: Seq Char -> Maybe Char Source #

map :: (Char -> Char) -> Seq Char -> Seq Char Source #

concatMap :: (Char -> Seq Char) -> Seq Char -> Seq Char Source #

toString :: (Seq Char -> String) -> Seq Char -> String Source #

toText :: (Seq Char -> Text) -> Seq Char -> Text Source #

any :: (Char -> Bool) -> Seq Char -> Bool Source #

all :: (Char -> Bool) -> Seq Char -> Bool Source #

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

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

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

scanl :: (Char -> Char -> Char) -> Char -> Seq Char -> Seq Char Source #

scanl1 :: (Char -> Char -> Char) -> Seq Char -> Seq Char Source #

scanr :: (Char -> Char -> Char) -> Char -> Seq Char -> Seq Char Source #

scanr1 :: (Char -> Char -> Char) -> Seq Char -> Seq Char Source #

mapAccumL :: (a -> Char -> (a, Char)) -> a -> Seq Char -> (a, Seq Char) Source #

mapAccumR :: (a -> Char -> (a, Char)) -> a -> Seq Char -> (a, Seq Char) Source #

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

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

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

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

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

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

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

find :: (Char -> Bool) -> Seq Char -> Maybe Char Source #

elem :: Char -> Seq Char -> Bool Source #

foldl_ :: (a -> Char -> a) -> a -> Seq Char -> a Source #

foldl_' :: (a -> Char -> a) -> a -> Seq Char -> a Source #

foldr_ :: (Char -> a -> a) -> a -> Seq Char -> a Source #

takeWhile_ :: Bool -> (Char -> Bool) -> Seq Char -> Seq Char Source #

dropWhile_ :: Bool -> (Char -> Bool) -> Seq Char -> Seq Char Source #

break_ :: Bool -> (Char -> Bool) -> Seq Char -> (Seq Char, Seq Char) Source #

span_ :: Bool -> (Char -> Bool) -> Seq Char -> (Seq Char, Seq Char) Source #

spanMaybe_ :: s -> (s -> Char -> Maybe s) -> Seq Char -> (Seq Char, Seq Char, s) Source #

spanMaybe_' :: s -> (s -> Char -> Maybe s) -> Seq Char -> (Seq Char, Seq Char, s) Source #

(Eq a, TextualMonoid a, StableFactorial a, PositiveMonoid a) => TextualMonoid (Concat a) Source # 
Instance details

Defined in Data.Monoid.Instances.Concat

Methods

fromText :: Text -> Concat a Source #

singleton :: Char -> Concat a Source #

splitCharacterPrefix :: Concat a -> Maybe (Char, Concat a) Source #

characterPrefix :: Concat a -> Maybe Char Source #

map :: (Char -> Char) -> Concat a -> Concat a Source #

concatMap :: (Char -> Concat a) -> Concat a -> Concat a Source #

toString :: (Concat a -> String) -> Concat a -> String Source #

toText :: (Concat a -> Text) -> Concat a -> Text Source #

any :: (Char -> Bool) -> Concat a -> Bool Source #

all :: (Char -> Bool) -> Concat a -> Bool Source #

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

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

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

scanl :: (Char -> Char -> Char) -> Char -> Concat a -> Concat a Source #

scanl1 :: (Char -> Char -> Char) -> Concat a -> Concat a Source #

scanr :: (Char -> Char -> Char) -> Char -> Concat a -> Concat a Source #

scanr1 :: (Char -> Char -> Char) -> Concat a -> Concat a Source #

mapAccumL :: (a0 -> Char -> (a0, Char)) -> a0 -> Concat a -> (a0, Concat a) Source #

mapAccumR :: (a0 -> Char -> (a0, Char)) -> a0 -> Concat a -> (a0, Concat a) Source #

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

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

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

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

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

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

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

find :: (Char -> Bool) -> Concat a -> Maybe Char Source #

elem :: Char -> Concat a -> Bool Source #

foldl_ :: (a0 -> Char -> a0) -> a0 -> Concat a -> a0 Source #

foldl_' :: (a0 -> Char -> a0) -> a0 -> Concat a -> a0 Source #

foldr_ :: (Char -> a0 -> a0) -> a0 -> Concat a -> a0 Source #

takeWhile_ :: Bool -> (Char -> Bool) -> Concat a -> Concat a Source #

dropWhile_ :: Bool -> (Char -> Bool) -> Concat a -> Concat a Source #

break_ :: Bool -> (Char -> Bool) -> Concat a -> (Concat a, Concat a) Source #

span_ :: Bool -> (Char -> Bool) -> Concat a -> (Concat a, Concat a) Source #

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

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

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

Defined in Data.Monoid.Instances.Measured

Methods

fromText :: Text -> Measured a Source #

singleton :: Char -> Measured a Source #

splitCharacterPrefix :: Measured a -> Maybe (Char, Measured a) Source #

characterPrefix :: Measured a -> Maybe Char Source #

map :: (Char -> Char) -> Measured a -> Measured a Source #

concatMap :: (Char -> Measured a) -> Measured a -> Measured a Source #

toString :: (Measured a -> String) -> Measured a -> String Source #

toText :: (Measured a -> Text) -> Measured a -> Text Source #

any :: (Char -> Bool) -> Measured a -> Bool Source #

all :: (Char -> Bool) -> Measured a -> Bool Source #

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

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

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

scanl :: (Char -> Char -> Char) -> Char -> Measured a -> Measured a Source #

scanl1 :: (Char -> Char -> Char) -> Measured a -> Measured a Source #

scanr :: (Char -> Char -> Char) -> Char -> Measured a -> Measured a Source #

scanr1 :: (Char -> Char -> Char) -> Measured a -> Measured a Source #

mapAccumL :: (a0 -> Char -> (a0, Char)) -> a0 -> Measured a -> (a0, Measured a) Source #

mapAccumR :: (a0 -> Char -> (a0, Char)) -> a0 -> Measured a -> (a0, Measured a) Source #

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

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

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

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

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

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

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

find :: (Char -> Bool) -> Measured a -> Maybe Char Source #

elem :: Char -> Measured a -> Bool Source #

foldl_ :: (a0 -> Char -> a0) -> a0 -> Measured a -> a0 Source #

foldl_' :: (a0 -> Char -> a0) -> a0 -> Measured a -> a0 Source #

foldr_ :: (Char -> a0 -> a0) -> a0 -> Measured a -> a0 Source #

takeWhile_ :: Bool -> (Char -> Bool) -> Measured a -> Measured a Source #

dropWhile_ :: Bool -> (Char -> Bool) -> Measured a -> Measured a Source #

break_ :: Bool -> (Char -> Bool) -> Measured a -> (Measured a, Measured a) Source #

span_ :: Bool -> (Char -> Bool) -> Measured a -> (Measured a, Measured a) Source #

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

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

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

Defined in Data.Monoid.Instances.Positioned

Methods

fromText :: Text -> LinePositioned m Source #

singleton :: Char -> LinePositioned m Source #

splitCharacterPrefix :: LinePositioned m -> Maybe (Char, LinePositioned m) Source #

characterPrefix :: LinePositioned m -> Maybe Char Source #

map :: (Char -> Char) -> LinePositioned m -> LinePositioned m Source #

concatMap :: (Char -> LinePositioned m) -> LinePositioned m -> LinePositioned m Source #

toString :: (LinePositioned m -> String) -> LinePositioned m -> String Source #

toText :: (LinePositioned m -> Text) -> LinePositioned m -> Text Source #

any :: (Char -> Bool) -> LinePositioned m -> Bool Source #

all :: (Char -> Bool) -> LinePositioned m -> Bool Source #

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

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

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

scanl :: (Char -> Char -> Char) -> Char -> LinePositioned m -> LinePositioned m Source #

scanl1 :: (Char -> Char -> Char) -> LinePositioned m -> LinePositioned m Source #

scanr :: (Char -> Char -> Char) -> Char -> LinePositioned m -> LinePositioned m Source #

scanr1 :: (Char -> Char -> Char) -> LinePositioned m -> LinePositioned m Source #

mapAccumL :: (a -> Char -> (a, Char)) -> a -> LinePositioned m -> (a, LinePositioned m) Source #

mapAccumR :: (a -> Char -> (a, Char)) -> a -> LinePositioned m -> (a, LinePositioned m) Source #

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

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

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

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

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

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

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

find :: (Char -> Bool) -> LinePositioned m -> Maybe Char Source #

elem :: Char -> LinePositioned m -> Bool Source #

foldl_ :: (a -> Char -> a) -> a -> LinePositioned m -> a Source #

foldl_' :: (a -> Char -> a) -> a -> LinePositioned m -> a Source #

foldr_ :: (Char -> a -> a) -> a -> LinePositioned m -> a Source #

takeWhile_ :: Bool -> (Char -> Bool) -> LinePositioned m -> LinePositioned m Source #

dropWhile_ :: Bool -> (Char -> Bool) -> LinePositioned m -> LinePositioned m Source #

break_ :: Bool -> (Char -> Bool) -> LinePositioned m -> (LinePositioned m, LinePositioned m) Source #

span_ :: Bool -> (Char -> Bool) -> LinePositioned m -> (LinePositioned m, LinePositioned m) Source #

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

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

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

Defined in Data.Monoid.Instances.Positioned

Methods

fromText :: Text -> OffsetPositioned m Source #

singleton :: Char -> OffsetPositioned m Source #

splitCharacterPrefix :: OffsetPositioned m -> Maybe (Char, OffsetPositioned m) Source #

characterPrefix :: OffsetPositioned m -> Maybe Char Source #

map :: (Char -> Char) -> OffsetPositioned m -> OffsetPositioned m Source #

concatMap :: (Char -> OffsetPositioned m) -> OffsetPositioned m -> OffsetPositioned m Source #

toString :: (OffsetPositioned m -> String) -> OffsetPositioned m -> String Source #

toText :: (OffsetPositioned m -> Text) -> OffsetPositioned m -> Text Source #

any :: (Char -> Bool) -> OffsetPositioned m -> Bool Source #

all :: (Char -> Bool) -> OffsetPositioned m -> Bool Source #

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

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

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

scanl :: (Char -> Char -> Char) -> Char -> OffsetPositioned m -> OffsetPositioned m Source #

scanl1 :: (Char -> Char -> Char) -> OffsetPositioned m -> OffsetPositioned m Source #

scanr :: (Char -> Char -> Char) -> Char -> OffsetPositioned m -> OffsetPositioned m Source #

scanr1 :: (Char -> Char -> Char) -> OffsetPositioned m -> OffsetPositioned m Source #

mapAccumL :: (a -> Char -> (a, Char)) -> a -> OffsetPositioned m -> (a, OffsetPositioned m) Source #

mapAccumR :: (a -> Char -> (a, Char)) -> a -> OffsetPositioned m -> (a, OffsetPositioned m) Source #

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

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

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

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

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

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

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

find :: (Char -> Bool) -> OffsetPositioned m -> Maybe Char Source #

elem :: Char -> OffsetPositioned m -> Bool Source #

foldl_ :: (a -> Char -> a) -> a -> OffsetPositioned m -> a Source #

foldl_' :: (a -> Char -> a) -> a -> OffsetPositioned m -> a Source #

foldr_ :: (Char -> a -> a) -> a -> OffsetPositioned m -> a Source #

takeWhile_ :: Bool -> (Char -> Bool) -> OffsetPositioned m -> OffsetPositioned m Source #

dropWhile_ :: Bool -> (Char -> Bool) -> OffsetPositioned m -> OffsetPositioned m Source #

break_ :: Bool -> (Char -> Bool) -> OffsetPositioned m -> (OffsetPositioned m, OffsetPositioned m) Source #

span_ :: Bool -> (Char -> Bool) -> OffsetPositioned m -> (OffsetPositioned m, OffsetPositioned m) Source #

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

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

TextualMonoid (Vector Char) Source # 
Instance details

Defined in Data.Monoid.Instances.CharVector

Methods

fromText :: Text -> Vector Char Source #

singleton :: Char -> Vector Char Source #

splitCharacterPrefix :: Vector Char -> Maybe (Char, Vector Char) Source #

characterPrefix :: Vector Char -> Maybe Char Source #

map :: (Char -> Char) -> Vector Char -> Vector Char Source #

concatMap :: (Char -> Vector Char) -> Vector Char -> Vector Char Source #

toString :: (Vector Char -> String) -> Vector Char -> String Source #

toText :: (Vector Char -> Text) -> Vector Char -> Text Source #

any :: (Char -> Bool) -> Vector Char -> Bool Source #

all :: (Char -> Bool) -> Vector Char -> Bool Source #

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

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

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

scanl :: (Char -> Char -> Char) -> Char -> Vector Char -> Vector Char Source #

scanl1 :: (Char -> Char -> Char) -> Vector Char -> Vector Char Source #

scanr :: (Char -> Char -> Char) -> Char -> Vector Char -> Vector Char Source #

scanr1 :: (Char -> Char -> Char) -> Vector Char -> Vector Char Source #

mapAccumL :: (a -> Char -> (a, Char)) -> a -> Vector Char -> (a, Vector Char) Source #

mapAccumR :: (a -> Char -> (a, Char)) -> a -> Vector Char -> (a, Vector Char) Source #

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

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

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

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

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

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

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

find :: (Char -> Bool) -> Vector Char -> Maybe Char Source #

elem :: Char -> Vector Char -> Bool Source #

foldl_ :: (a -> Char -> a) -> a -> Vector Char -> a Source #

foldl_' :: (a -> Char -> a) -> a -> Vector Char -> a Source #

foldr_ :: (Char -> a -> a) -> a -> Vector Char -> a Source #

takeWhile_ :: Bool -> (Char -> Bool) -> Vector Char -> Vector Char Source #

dropWhile_ :: Bool -> (Char -> Bool) -> Vector Char -> Vector Char Source #

break_ :: Bool -> (Char -> Bool) -> Vector Char -> (Vector Char, Vector Char) Source #

span_ :: Bool -> (Char -> Bool) -> Vector Char -> (Vector Char, Vector Char) Source #

spanMaybe_ :: s -> (s -> Char -> Maybe s) -> Vector Char -> (Vector Char, Vector Char, s) Source #

spanMaybe_' :: s -> (s -> Char -> Maybe s) -> Vector Char -> (Vector Char, Vector Char, s) Source #

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

Defined in Data.Monoid.Instances.Stateful

Methods

fromText :: Text -> Stateful a b Source #

singleton :: Char -> Stateful a b Source #

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

characterPrefix :: Stateful a b -> Maybe Char Source #

map :: (Char -> Char) -> Stateful a b -> Stateful a b Source #

concatMap :: (Char -> Stateful a b) -> Stateful a b -> Stateful a b Source #

toString :: (Stateful a b -> String) -> Stateful a b -> String Source #

toText :: (Stateful a b -> Text) -> Stateful a b -> Text Source #

any :: (Char -> Bool) -> Stateful a b -> Bool Source #

all :: (Char -> Bool) -> Stateful a b -> Bool Source #

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

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

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

scanl :: (Char -> Char -> Char) -> Char -> Stateful a b -> Stateful a b Source #

scanl1 :: (Char -> Char -> Char) -> Stateful a b -> Stateful a b Source #

scanr :: (Char -> Char -> Char) -> Char -> Stateful a b -> Stateful a b Source #

scanr1 :: (Char -> Char -> Char) -> Stateful a b -> Stateful a b Source #

mapAccumL :: (a0 -> Char -> (a0, Char)) -> a0 -> Stateful a b -> (a0, Stateful a b) Source #

mapAccumR :: (a0 -> Char -> (a0, Char)) -> a0 -> Stateful a b -> (a0, Stateful a b) Source #

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

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

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

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

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

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

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

find :: (Char -> Bool) -> Stateful a b -> Maybe Char Source #

elem :: Char -> Stateful a b -> Bool Source #

foldl_ :: (a0 -> Char -> a0) -> a0 -> Stateful a b -> a0 Source #

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

foldr_ :: (Char -> a0 -> a0) -> a0 -> Stateful a b -> a0 Source #

takeWhile_ :: Bool -> (Char -> Bool) -> Stateful a b -> Stateful a b Source #

dropWhile_ :: Bool -> (Char -> Bool) -> Stateful a b -> Stateful a b Source #

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

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

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

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