module Control.Foldl.Text (
fold
, head
, last
, null
, length
, any
, all
, maximum
, minimum
, elem
, notElem
, find
, index
, elemIndex
, findIndex
, count
, module Control.Foldl
, module Data.Text
) where
import Control.Foldl (Fold)
import Control.Foldl.Internal (Maybe'(..), lazy, strict, Either'(..), hush)
import qualified Control.Foldl as L
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Lazy as Lazy
import Prelude hiding (
head, last, null, length, any, all, maximum, minimum, elem, notElem )
fold :: Fold Text a -> Lazy.Text -> a
fold (L.Fold step begin done) as = done (Lazy.foldlChunks step begin as)
head :: Fold Text (Maybe Char)
head = L.Fold step Nothing' lazy
where
step mc txt =
if T.null txt
then mc
else case mc of
Just' _ -> mc
Nothing' -> Just' (T.head txt)
last :: Fold Text (Maybe Char)
last = L.Fold step Nothing' lazy
where
step mc txt =
if T.null txt
then mc
else Just' (T.last txt)
null :: Fold Text Bool
null = L.Fold step True id
where
step isNull txt = isNull && T.null txt
length :: Num n => Fold Text n
length = L.Fold (\n txt -> n + fromIntegral (T.length txt)) 0 id
all :: (Char -> Bool) -> Fold Text Bool
all predicate = L.Fold (\b txt -> b && T.all predicate txt) True id
any :: (Char -> Bool) -> Fold Text Bool
any predicate = L.Fold (\b txt -> b || T.any predicate txt) False id
maximum :: Fold Text (Maybe Char)
maximum = L.Fold step Nothing' lazy
where
step mc txt =
if T.null txt
then mc
else Just' (case mc of
Nothing' -> T.maximum txt
Just' c -> max c (T.maximum txt) )
minimum :: Fold Text (Maybe Char)
minimum = L.Fold step Nothing' lazy
where
step mc txt =
if T.null txt
then mc
else Just' (case mc of
Nothing' -> T.minimum txt
Just' c -> min c (T.minimum txt) )
elem :: Char -> Fold Text Bool
elem c = any (c ==)
notElem :: Char -> Fold Text Bool
notElem c = all (c /=)
find :: (Char -> Bool) -> Fold Text (Maybe Char)
find predicate = L.Fold step Nothing' lazy
where
step mc txt = case mc of
Nothing' -> strict (T.find predicate txt)
Just' _ -> mc
index :: Integral n => n -> Fold Text (Maybe Char)
index i = L.Fold step (Left' (fromIntegral i)) hush
where
step x txt = case x of
Left' remainder ->
let len = T.length txt
in if remainder < len
then Right' (T.index txt remainder)
else Left' (remainder len)
_ -> x
elemIndex :: Num n => Char -> Fold Text (Maybe n)
elemIndex c = findIndex (c ==)
findIndex :: Num n => (Char -> Bool) -> Fold Text (Maybe n)
findIndex predicate = L.Fold step (Left' 0) hush
where
step x txt = case x of
Left' m -> case T.findIndex predicate txt of
Nothing -> Left' (m + fromIntegral (T.length txt))
Just n -> Right' (m + fromIntegral n)
_ -> x
count :: Num n => Char -> Fold Text n
count c = L.Fold step 0 id
where
step n txt = n + fromIntegral (T.count (T.singleton c) txt)