module Data.JSString.Internal.Fusion (
Stream(..)
, Step(..)
, stream
, unstream
, reverseStream
, length
, reverse
, reverseScanr
, mapAccumL
, unfoldrN
, index
, findIndex
, countChar
) where
import Prelude hiding (length, reverse)
import Data.JSString.Internal.Type
import qualified Data.Text.Internal.Fusion as T
import Data.Text.Internal.Fusion (Stream(..), Step(..))
stream :: JSString -> Stream Char
stream (JSString t) = T.stream t
{-# INLINE [0] stream #-}
reverseStream :: JSString -> Stream Char
reverseStream (JSString x) = T.reverseStream x
{-# INLINE [0] reverseStream #-}
unstream :: Stream Char -> JSString
unstream strm = JSString $ T.unstream strm
{-# INLINE [0] unstream #-}
{-# RULES "STREAM stream/unstream fusion" forall s. stream (unstream s) = s #-}
length :: Stream Char -> Int
length = T.length
{-# INLINE[0] length #-}
reverse :: Stream Char -> JSString
reverse = JSString . T.reverse
{-# INLINE [0] reverse #-}
reverseScanr :: (Char -> Char -> Char) -> Char -> Stream Char -> Stream Char
reverseScanr = T.reverseScanr
{-# INLINE reverseScanr #-}
unfoldrN :: Int -> (a -> Maybe (Char,a)) -> a -> Stream Char
unfoldrN = T.unfoldrN
{-# INLINE [0] unfoldrN #-}
index :: Stream Char -> Int -> Char
index = T.index
{-# INLINE [0] index #-}
findIndex :: (Char -> Bool) -> Stream Char -> Maybe Int
findIndex = T.findIndex
{-# INLINE [0] findIndex #-}
countChar :: Char -> Stream Char -> Int
countChar = T.countChar
{-# INLINE [0] countChar #-}
mapAccumL :: (a -> Char -> (a, Char)) -> a -> Stream Char -> (a, JSString)
mapAccumL f z strm = JSString <$> T.mapAccumL f z strm
{-# INLINE [0] mapAccumL #-}