foldl-1.2.4: Composable, streaming, and efficient left folds

Safe HaskellSafe
LanguageHaskell98

Control.Foldl.Text

Contents

Description

Folds for text streams

Synopsis

Folding

fold :: Fold Text a -> Text -> a Source #

Apply a strict left Fold to lazy text

foldM :: Monad m => FoldM m Text a -> Text -> m a Source #

Apply a strict monadic left FoldM to lazy text

Folds

head :: Fold Text (Maybe Char) Source #

Get the first character of a text stream or return Nothing if the stream is empty

last :: Fold Text (Maybe Char) Source #

Get the last character of a text stream or return Nothing if the text stream is empty

null :: Fold Text Bool Source #

Returns True if the text stream is empty, False otherwise

length :: Num n => Fold Text n Source #

Return the length of the text stream in characters

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

(any predicate) returns True if any character satisfies the predicate, False otherwise

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

(all predicate) returns True if all characters satisfy the predicate, False otherwise

maximum :: Fold Text (Maybe Char) Source #

Computes the maximum character

minimum :: Fold Text (Maybe Char) Source #

Computes the minimum character

elem :: Char -> Fold Text Bool Source #

(elem c) returns True if the text stream has a character equal to c, False otherwise

notElem :: Char -> Fold Text Bool Source #

(notElem c) returns False if the text stream has a character equal to c, True otherwise

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

(find predicate) returns the first character that satisfies the predicate or Nothing if no character satisfies the predicate

index :: Integral n => n -> Fold Text (Maybe Char) Source #

(index n) returns the nth character of the text stream, or Nothing if the stream has an insufficient number of characters

elemIndex :: Num n => Char -> Fold Text (Maybe n) Source #

(elemIndex c) returns the index of the first character that equals c, or Nothing if no character matches

findIndex :: Num n => (Char -> Bool) -> Fold Text (Maybe n) Source #

(findIndex predicate) returns the index of the first character that satisfies the predicate, or Nothing if no character satisfies the predicate

count :: Num n => Char -> Fold Text n Source #

(count c) returns the number of times c appears

lazy :: Fold Text Text Source #

Combine all the strict Text chunks to build a lazy Text

Re-exports

Control.Foldl re-exports the Fold type

Data.Text re-exports the Text type

module Data.Text