text-2.1.1: An efficient packed Unicode text type.
Copyright(c) Tom Harper 2008-2009
(c) Bryan O'Sullivan 2009-2010
(c) Duncan Coutts 2009
LicenseBSD-style
Maintainerbos@serpentine.com
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Data.Text.Internal.Fusion

Description

Warning: this is an internal module, and does not have a stable API or name. Functions in this module may not check or enforce preconditions expected by public modules. Use at your own risk!

Text manipulation functions represented as fusible operations over streams.

Synopsis

Types

data Stream a Source #

A co-recursive type yielding a single element at a time depending on the internal state it carries.

Constructors

Stream (s -> Step s a) !s !Size 

Instances

Instances details
Eq a => Eq (Stream a) Source # 
Instance details

Defined in Data.Text.Internal.Fusion.Types

Methods

(==) :: Stream a -> Stream a -> Bool Source #

(/=) :: Stream a -> Stream a -> Bool Source #

Ord a => Ord (Stream a) Source # 
Instance details

Defined in Data.Text.Internal.Fusion.Types

Methods

compare :: Stream a -> Stream a -> Ordering Source #

(<) :: Stream a -> Stream a -> Bool Source #

(<=) :: Stream a -> Stream a -> Bool Source #

(>) :: Stream a -> Stream a -> Bool Source #

(>=) :: Stream a -> Stream a -> Bool Source #

max :: Stream a -> Stream a -> Stream a Source #

min :: Stream a -> Stream a -> Stream a Source #

data Step s a Source #

Intermediate result in a processing pipeline.

Constructors

Done 
Skip !s 
Yield !a !s 

Creation and elimination

stream :: Text -> Stream Char Source #

O(n) Convert Text into a Stream Char.

Properties

unstream . stream = id
stream . unstream = id

unstream :: Stream Char -> Text Source #

O(n) Convert Stream Char into a Text.

Properties

unstream . stream = id
stream . unstream = id

reverseStream :: Text -> Stream Char Source #

O(n) Converts Text into a Stream Char, but iterates backwards through the text.

Properties

unstream . reverseStream = reverse

length :: Stream Char -> Int Source #

O(n) Returns the number of characters in a Stream.

Properties

length . stream = length

Transformations

reverse :: Stream Char -> Text Source #

O(n) Reverse the characters of a Stream returning Text.

Properties

reverse . stream = reverse

Construction

Scans

reverseScanr :: (Char -> Char -> Char) -> Char -> Stream Char -> Stream Char Source #

O(n) Perform the equivalent of scanr over a list, only with the input and result reversed.

Properties

reverse . reverseScanr f c . reverseStream = scanr f c

Accumulating maps

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

O(n) Like a combination of map and foldl'. Applies a function to each element of a Text, passing an accumulating parameter from left to right, and returns a final Text.

Properties

mapAccumL g z0 . stream = mapAccumL g z0

Generation and unfolding

unfoldrN :: Int -> (a -> Maybe (Char, a)) -> a -> Stream Char Source #

O(n) Like unfoldr, unfoldrN builds a stream from a seed value. However, the length of the result is limited by the first argument to unfoldrN. This function is more efficient than unfoldr when the length of the result is known.

Properties

unstream (unfoldrN n f a) = unfoldrN n f a

Indexing

index :: HasCallStack => Stream Char -> Int -> Char Source #

O(n) stream index (subscript) operator, starting from 0.

Properties

index (stream t) n  = index t n

findIndex :: (Char -> Bool) -> Stream Char -> Maybe Int Source #

The findIndex function takes a predicate and a stream and returns the index of the first element in the stream satisfying the predicate.

Properties

findIndex p . stream  = findIndex p

countChar :: Char -> Stream Char -> Int Source #

O(n) The count function returns the number of times the query element appears in the given stream.

Properties

countChar c . stream  = countChar c