module Data.Text.Internal.Lazy.Fusion
(
stream
, unstream
, unstreamChunks
, length
, unfoldrN
, index
, countChar
) where
import Prelude hiding (length)
import qualified Data.Text.Internal.Fusion.Common as S
import Control.Monad.ST (runST)
import Data.Text.Internal.Fusion.Types
import Data.Text.Internal.Fusion.Size (isEmpty, unknownSize)
import Data.Text.Internal.Lazy
import qualified Data.Text.Internal as I
import qualified Data.Text.Array as A
import Data.Text.Internal.Unsafe.Char (unsafeWrite)
import Data.Text.Internal.Unsafe.Shift (shiftL)
import Data.Text.Unsafe (Iter(..), iter)
import Data.Int (Int64)
default(Int64)
stream :: Text -> Stream Char
stream text = Stream next (text :*: 0) unknownSize
where
next (Empty :*: _) = Done
next (txt@(Chunk t@(I.Text _ _ len) ts) :*: i)
| i >= len = next (ts :*: 0)
| otherwise = Yield c (txt :*: i+d)
where Iter c d = iter t i
unstreamChunks :: Int -> Stream Char -> Text
unstreamChunks !chunkSize (Stream next s0 len0)
| isEmpty len0 = Empty
| otherwise = outer s0
where
outer so =
case next so of
Done -> Empty
Skip s' -> outer s'
Yield x s' -> runST $ do
a <- A.new unknownLength
unsafeWrite a 0 x >>= inner a unknownLength s'
where unknownLength = 4
where
inner marr !len s !i
| i + 1 >= chunkSize = finish marr i s
| i + 1 >= len = do
let newLen = min (len `shiftL` 1) chunkSize
marr' <- A.new newLen
A.copyM marr' 0 marr 0 len
inner marr' newLen s i
| otherwise =
case next s of
Done -> finish marr i s
Skip s' -> inner marr len s' i
Yield x s' -> do d <- unsafeWrite marr i x
inner marr len s' (i+d)
finish marr len s' = do
arr <- A.unsafeFreeze marr
return (I.Text arr 0 len `Chunk` outer s')
unstream :: Stream Char -> Text
unstream = unstreamChunks defaultChunkSize
length :: Stream Char -> Int64
length = S.lengthI
unfoldrN :: Int64 -> (a -> Maybe (Char,a)) -> a -> Stream Char
unfoldrN n = S.unfoldrNI n
index :: Stream Char -> Int64 -> Char
index = S.indexI
countChar :: Char -> Stream Char -> Int64
countChar = S.countCharI