module Control.Foldl.Text (
fold
, foldM
, head
, last
, null
, length
, any
, all
, maximum
, minimum
, elem
, notElem
, find
, index
, elemIndex
, findIndex
, count
, lazy
, module Control.Foldl
, module Data.Text
) where
import Control.Foldl (Fold, FoldM)
import Control.Foldl.Internal (Maybe'(..), strict, Either'(..), hush)
import Data.Text (Text)
import Prelude hiding (
head, last, null, length, any, all, maximum, minimum, elem, notElem )
import qualified Control.Foldl
import qualified Control.Foldl.Internal
import qualified Data.Text
import qualified Data.Text.Lazy
fold :: Fold Text a -> Data.Text.Lazy.Text -> a
fold :: forall a. Fold Text a -> Text -> a
fold (Control.Foldl.Fold x -> Text -> x
step x
begin x -> a
done) Text
as =
x -> a
done ((x -> Text -> x) -> x -> Text -> x
forall a. (a -> Text -> a) -> a -> Text -> a
Data.Text.Lazy.foldlChunks x -> Text -> x
step x
begin Text
as)
{-# INLINABLE fold #-}
foldM :: Monad m => FoldM m Text a -> Data.Text.Lazy.Text -> m a
foldM :: forall (m :: * -> *) a. Monad m => FoldM m Text a -> Text -> m a
foldM (Control.Foldl.FoldM x -> Text -> m x
step m x
begin x -> m a
done) Text
as = do
x
x <- (m x -> Text -> m x) -> m x -> Text -> m x
forall a. (a -> Text -> a) -> a -> Text -> a
Data.Text.Lazy.foldlChunks m x -> Text -> m x
step' m x
begin Text
as
x -> m a
done x
x
where
step' :: m x -> Text -> m x
step' m x
mx Text
bs = do
x
x <- m x
mx
x
x x -> m x -> m x
forall a b. a -> b -> b
`seq` x -> Text -> m x
step x
x Text
bs
{-# INLINABLE foldM #-}
head :: Fold Text (Maybe Char)
head :: Fold Text (Maybe Char)
head = (Maybe' Char -> Text -> Maybe' Char)
-> Maybe' Char
-> (Maybe' Char -> Maybe Char)
-> Fold Text (Maybe Char)
forall a b x. (x -> a -> x) -> x -> (x -> b) -> Fold a b
Control.Foldl.Fold Maybe' Char -> Text -> Maybe' Char
step Maybe' Char
forall a. Maybe' a
Nothing' Maybe' Char -> Maybe Char
forall a. Maybe' a -> Maybe a
Control.Foldl.Internal.lazy
where
step :: Maybe' Char -> Text -> Maybe' Char
step Maybe' Char
mc Text
txt =
if Text -> Bool
Data.Text.null Text
txt
then Maybe' Char
mc
else case Maybe' Char
mc of
Just' Char
_ -> Maybe' Char
mc
Maybe' Char
Nothing' -> Char -> Maybe' Char
forall a. a -> Maybe' a
Just' (HasCallStack => Text -> Char
Text -> Char
Data.Text.head Text
txt)
{-# INLINABLE head #-}
last :: Fold Text (Maybe Char)
last :: Fold Text (Maybe Char)
last = (Maybe' Char -> Text -> Maybe' Char)
-> Maybe' Char
-> (Maybe' Char -> Maybe Char)
-> Fold Text (Maybe Char)
forall a b x. (x -> a -> x) -> x -> (x -> b) -> Fold a b
Control.Foldl.Fold Maybe' Char -> Text -> Maybe' Char
step Maybe' Char
forall a. Maybe' a
Nothing' Maybe' Char -> Maybe Char
forall a. Maybe' a -> Maybe a
Control.Foldl.Internal.lazy
where
step :: Maybe' Char -> Text -> Maybe' Char
step Maybe' Char
mc Text
txt =
if Text -> Bool
Data.Text.null Text
txt
then Maybe' Char
mc
else Char -> Maybe' Char
forall a. a -> Maybe' a
Just' (HasCallStack => Text -> Char
Text -> Char
Data.Text.last Text
txt)
{-# INLINABLE last #-}
null :: Fold Text Bool
null :: Fold Text Bool
null = (Bool -> Text -> Bool) -> Bool -> (Bool -> Bool) -> Fold Text Bool
forall a b x. (x -> a -> x) -> x -> (x -> b) -> Fold a b
Control.Foldl.Fold Bool -> Text -> Bool
step Bool
True Bool -> Bool
forall a. a -> a
id
where
step :: Bool -> Text -> Bool
step Bool
isNull Text
txt = Bool
isNull Bool -> Bool -> Bool
&& Text -> Bool
Data.Text.null Text
txt
{-# INLINABLE null #-}
length :: Num n => Fold Text n
length :: forall n. Num n => Fold Text n
length =
(n -> Text -> n) -> n -> (n -> n) -> Fold Text n
forall a b x. (x -> a -> x) -> x -> (x -> b) -> Fold a b
Control.Foldl.Fold (\n
n Text
txt -> n
n n -> n -> n
forall a. Num a => a -> a -> a
+ Int -> n
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Text -> Int
Data.Text.length Text
txt)) n
0 n -> n
forall a. a -> a
id
{-# INLINABLE length #-}
all :: (Char -> Bool) -> Fold Text Bool
all :: (Char -> Bool) -> Fold Text Bool
all Char -> Bool
predicate =
(Bool -> Text -> Bool) -> Bool -> (Bool -> Bool) -> Fold Text Bool
forall a b x. (x -> a -> x) -> x -> (x -> b) -> Fold a b
Control.Foldl.Fold (\Bool
b Text
txt -> Bool
b Bool -> Bool -> Bool
&& (Char -> Bool) -> Text -> Bool
Data.Text.all Char -> Bool
predicate Text
txt) Bool
True Bool -> Bool
forall a. a -> a
id
{-# INLINABLE all #-}
any :: (Char -> Bool) -> Fold Text Bool
any :: (Char -> Bool) -> Fold Text Bool
any Char -> Bool
predicate =
(Bool -> Text -> Bool) -> Bool -> (Bool -> Bool) -> Fold Text Bool
forall a b x. (x -> a -> x) -> x -> (x -> b) -> Fold a b
Control.Foldl.Fold (\Bool
b Text
txt -> Bool
b Bool -> Bool -> Bool
|| (Char -> Bool) -> Text -> Bool
Data.Text.any Char -> Bool
predicate Text
txt) Bool
False Bool -> Bool
forall a. a -> a
id
{-# INLINABLE any #-}
maximum :: Fold Text (Maybe Char)
maximum :: Fold Text (Maybe Char)
maximum = (Maybe' Char -> Text -> Maybe' Char)
-> Maybe' Char
-> (Maybe' Char -> Maybe Char)
-> Fold Text (Maybe Char)
forall a b x. (x -> a -> x) -> x -> (x -> b) -> Fold a b
Control.Foldl.Fold Maybe' Char -> Text -> Maybe' Char
step Maybe' Char
forall a. Maybe' a
Nothing' Maybe' Char -> Maybe Char
forall a. Maybe' a -> Maybe a
Control.Foldl.Internal.lazy
where
step :: Maybe' Char -> Text -> Maybe' Char
step Maybe' Char
mc Text
txt =
if Text -> Bool
Data.Text.null Text
txt
then Maybe' Char
mc
else Char -> Maybe' Char
forall a. a -> Maybe' a
Just' (case Maybe' Char
mc of
Maybe' Char
Nothing' -> HasCallStack => Text -> Char
Text -> Char
Data.Text.maximum Text
txt
Just' Char
c -> Char -> Char -> Char
forall a. Ord a => a -> a -> a
max Char
c (HasCallStack => Text -> Char
Text -> Char
Data.Text.maximum Text
txt) )
{-# INLINABLE maximum #-}
minimum :: Fold Text (Maybe Char)
minimum :: Fold Text (Maybe Char)
minimum = (Maybe' Char -> Text -> Maybe' Char)
-> Maybe' Char
-> (Maybe' Char -> Maybe Char)
-> Fold Text (Maybe Char)
forall a b x. (x -> a -> x) -> x -> (x -> b) -> Fold a b
Control.Foldl.Fold Maybe' Char -> Text -> Maybe' Char
step Maybe' Char
forall a. Maybe' a
Nothing' Maybe' Char -> Maybe Char
forall a. Maybe' a -> Maybe a
Control.Foldl.Internal.lazy
where
step :: Maybe' Char -> Text -> Maybe' Char
step Maybe' Char
mc Text
txt =
if Text -> Bool
Data.Text.null Text
txt
then Maybe' Char
mc
else Char -> Maybe' Char
forall a. a -> Maybe' a
Just' (case Maybe' Char
mc of
Maybe' Char
Nothing' -> HasCallStack => Text -> Char
Text -> Char
Data.Text.minimum Text
txt
Just' Char
c -> Char -> Char -> Char
forall a. Ord a => a -> a -> a
min Char
c (HasCallStack => Text -> Char
Text -> Char
Data.Text.minimum Text
txt) )
{-# INLINABLE minimum #-}
elem :: Char -> Fold Text Bool
elem :: Char -> Fold Text Bool
elem Char
c = (Char -> Bool) -> Fold Text Bool
any (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==)
{-# INLINABLE elem #-}
notElem :: Char -> Fold Text Bool
notElem :: Char -> Fold Text Bool
notElem Char
c = (Char -> Bool) -> Fold Text Bool
all (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=)
{-# INLINABLE notElem #-}
find :: (Char -> Bool) -> Fold Text (Maybe Char)
find :: (Char -> Bool) -> Fold Text (Maybe Char)
find Char -> Bool
predicate = (Maybe' Char -> Text -> Maybe' Char)
-> Maybe' Char
-> (Maybe' Char -> Maybe Char)
-> Fold Text (Maybe Char)
forall a b x. (x -> a -> x) -> x -> (x -> b) -> Fold a b
Control.Foldl.Fold Maybe' Char -> Text -> Maybe' Char
step Maybe' Char
forall a. Maybe' a
Nothing' Maybe' Char -> Maybe Char
forall a. Maybe' a -> Maybe a
Control.Foldl.Internal.lazy
where
step :: Maybe' Char -> Text -> Maybe' Char
step Maybe' Char
mc Text
txt = case Maybe' Char
mc of
Maybe' Char
Nothing' -> Maybe Char -> Maybe' Char
forall a. Maybe a -> Maybe' a
strict ((Char -> Bool) -> Text -> Maybe Char
Data.Text.find Char -> Bool
predicate Text
txt)
Just' Char
_ -> Maybe' Char
mc
{-# INLINABLE find #-}
index :: Integral n => n -> Fold Text (Maybe Char)
index :: forall n. Integral n => n -> Fold Text (Maybe Char)
index n
i = (Either' Int Char -> Text -> Either' Int Char)
-> Either' Int Char
-> (Either' Int Char -> Maybe Char)
-> Fold Text (Maybe Char)
forall a b x. (x -> a -> x) -> x -> (x -> b) -> Fold a b
Control.Foldl.Fold Either' Int Char -> Text -> Either' Int Char
step (Int -> Either' Int Char
forall a b. a -> Either' a b
Left' (n -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral n
i)) Either' Int Char -> Maybe Char
forall a b. Either' a b -> Maybe b
hush
where
step :: Either' Int Char -> Text -> Either' Int Char
step Either' Int Char
x Text
txt = case Either' Int Char
x of
Left' Int
remainder ->
let len :: Int
len = Text -> Int
Data.Text.length Text
txt
in if Int
remainder Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
len
then Char -> Either' Int Char
forall a b. b -> Either' a b
Right' (HasCallStack => Text -> Int -> Char
Text -> Int -> Char
Data.Text.index Text
txt Int
remainder)
else Int -> Either' Int Char
forall a b. a -> Either' a b
Left' (Int
remainder Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
len)
Either' Int Char
_ -> Either' Int Char
x
{-# INLINABLE index #-}
elemIndex :: Num n => Char -> Fold Text (Maybe n)
elemIndex :: forall n. Num n => Char -> Fold Text (Maybe n)
elemIndex Char
c = (Char -> Bool) -> Fold Text (Maybe n)
forall n. Num n => (Char -> Bool) -> Fold Text (Maybe n)
findIndex (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==)
{-# INLINABLE elemIndex #-}
findIndex :: Num n => (Char -> Bool) -> Fold Text (Maybe n)
findIndex :: forall n. Num n => (Char -> Bool) -> Fold Text (Maybe n)
findIndex Char -> Bool
predicate = (Either' n n -> Text -> Either' n n)
-> Either' n n -> (Either' n n -> Maybe n) -> Fold Text (Maybe n)
forall a b x. (x -> a -> x) -> x -> (x -> b) -> Fold a b
Control.Foldl.Fold Either' n n -> Text -> Either' n n
forall {b}. Num b => Either' b b -> Text -> Either' b b
step (n -> Either' n n
forall a b. a -> Either' a b
Left' n
0) Either' n n -> Maybe n
forall a b. Either' a b -> Maybe b
hush
where
step :: Either' b b -> Text -> Either' b b
step Either' b b
x Text
txt = case Either' b b
x of
Left' b
m -> case (Char -> Bool) -> Text -> Maybe Int
Data.Text.findIndex Char -> Bool
predicate Text
txt of
Maybe Int
Nothing -> b -> Either' b b
forall a b. a -> Either' a b
Left' (b
m b -> b -> b
forall a. Num a => a -> a -> a
+ Int -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Text -> Int
Data.Text.length Text
txt))
Just Int
n -> b -> Either' b b
forall a b. b -> Either' a b
Right' (b
m b -> b -> b
forall a. Num a => a -> a -> a
+ Int -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n)
Either' b b
_ -> Either' b b
x
{-# INLINABLE findIndex #-}
count :: Num n => Char -> Fold Text n
count :: forall n. Num n => Char -> Fold Text n
count Char
c = (n -> Text -> n) -> n -> (n -> n) -> Fold Text n
forall a b x. (x -> a -> x) -> x -> (x -> b) -> Fold a b
Control.Foldl.Fold n -> Text -> n
forall {a}. Num a => a -> Text -> a
step n
0 n -> n
forall a. a -> a
id
where
step :: a -> Text -> a
step a
n Text
txt = a
n a -> a -> a
forall a. Num a => a -> a -> a
+ Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (HasCallStack => Text -> Text -> Int
Text -> Text -> Int
Data.Text.count (Char -> Text
Data.Text.singleton Char
c) Text
txt)
{-# INLINABLE count #-}
lazy :: Fold Text Data.Text.Lazy.Text
lazy :: Fold Text Text
lazy = ([Text] -> Text) -> Fold Text [Text] -> Fold Text Text
forall a b. (a -> b) -> Fold Text a -> Fold Text b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Text] -> Text
Data.Text.Lazy.fromChunks Fold Text [Text]
forall a. Fold a [a]
Control.Foldl.list
{-# INLINABLE lazy #-}