module Z.Data.Text.Search (
elem, notElem
, findIndices
, find, findR
, findIndex
, findIndexR
, filter, partition
) where
import Control.Monad.ST
import Data.Word
import Prelude hiding (elem, notElem, filter)
import Z.Data.Array
import Z.Data.Text.Base
import Z.Data.Text.UTF8Codec
import qualified Z.Data.Vector.Base as V
findIndices :: (Char -> Bool) -> Text -> [Int]
{-# INLINE findIndices #-}
findIndices f (Text (V.PrimVector arr s l)) = go 0 s
where
!end = s + l
go !i !p | p >= end = []
| f x = i : go (i+1) (p+off)
| otherwise = go (i+1) (p+off)
where (# x, off #) = decodeChar arr p
find :: (Char -> Bool)
-> Text
-> (Int, Int, Maybe Char)
{-# INLINE find #-}
find f (Text (V.PrimVector arr s l)) = go 0 s
where
!end = s + l
go !i !j | j >= end = (i, j, Nothing)
| otherwise =
let (# x, off #) = decodeChar arr j
in if f x
then (i, j, Just x)
else go (i+1) (j+off)
findR :: (Char -> Bool)
-> Text
-> (Int, Int, Maybe Char)
{-# INLINE findR #-}
findR f (Text (V.PrimVector arr s l)) = go 0 (s+l-1)
where
go !i !j | j < s = (i, j, Nothing)
| otherwise =
let (# x, off #) = decodeCharReverse arr j
in if f x
then (i, j, Just x)
else go (i+1) (j-off)
findIndex :: (Char -> Bool) -> Text -> Int
{-# INLINE findIndex #-}
findIndex f t = case find f t of (_, i, _) -> i
findIndexR :: (Char -> Bool) -> Text -> Int
{-# INLINE findIndexR #-}
findIndexR f t = case findR f t of (_, i, _) -> i
filter :: (Char -> Bool) -> Text -> Text
{-# INLINE filter #-}
filter f (Text (V.PrimVector arr s l)) = Text (V.createN l (go s 0))
where
!end = s + l
go :: Int -> Int -> MutablePrimArray s Word8 -> ST s Int
go !i !j marr
| i >= end = return j
| otherwise =
let (# x, off #) = decodeChar arr i
in if f x
then do
copyChar off marr j arr i
go (i+off) (j+off) marr
else go (i+off) j marr
partition :: (Char -> Bool) -> Text -> (Text, Text)
{-# INLINE partition #-}
partition f (Text (V.PrimVector arr s l))
| l == 0 = (empty, empty)
| otherwise = let !(bs1, bs2) = V.createN2 l l (go 0 0 s) in (Text bs1, Text bs2)
where
!end = s + l
go :: Int -> Int -> Int -> MutablePrimArray s Word8 -> MutablePrimArray s Word8 -> ST s (Int, Int)
go !i !j !p !mba0 !mba1
| p >= end = return (i, j)
| otherwise =
let (# x, off #) = decodeChar arr p
in if f x
then copyChar off mba0 i arr p >> go (i+off) j (p+off) mba0 mba1
else copyChar off mba1 j arr p >> go i (j+off) (p+off) mba0 mba1
elem :: Char -> Text -> Bool
{-# INLINE elem #-}
elem x t = case find (x==) t of (_,_,Nothing) -> False
_ -> True
notElem :: Char -> Text -> Bool
{-# INLINE notElem #-}
notElem x = not . elem x