{-# LANGUAGE UnboxedTuples #-}

#include "inline.hs"

-- |
-- Module      : Streamly.Internal.Data.Array.Prim.Type
-- Copyright   : (c) 2020 Composewell Technologies
--
-- License     : BSD-3-Clause
-- Maintainer  : streamly@composewell.com
-- Stability   : experimental
-- Portability : GHC
--
module Streamly.Internal.Data.Array.Prim.Type
    (
      Array (..)
    , unsafeFreeze
    , unsafeFreezeWithShrink
--    , unsafeThaw
    , defaultChunkSize
    , nil

    -- * Construction
    , spliceTwo

    , fromList
    , fromListN
    , fromStreamDN
    , fromStreamD

    -- * Streams of arrays
    , fromStreamDArraysOf
    , FlattenState (..) -- for inspection testing
    , flattenArrays
    , flattenArraysRev
    , SpliceState (..) -- for inspection testing
    , packArraysChunksOf
    , lpackArraysChunksOf
#if !defined(mingw32_HOST_OS)
--    , groupIOVecsOf
#endif
    , splitOn
    , breakOn

    -- * Elimination
    , unsafeIndex
    , byteLength
    , length

    , foldl'
    , foldr
    , foldr'
    , foldlM'
    , splitAt

    , toStreamD
    , toStreamDRev
    , toStreamK
    , toStreamKRev
    , toList
--    , toArrayMinChunk
    , writeN
    , MA.ArrayUnsafe(..)
    , writeNUnsafe
    , write

    , unlines
    )
where

import qualified Streamly.Internal.Data.Array.Prim.Mut.Type as MA

#include "Streamly/Internal/Data/Array/Prim/TypesInclude.hs"

-- Drops the separator byte
-- Inefficient compared to Memory Array
{-# INLINE breakOn #-}
breakOn ::
       MonadIO m
    => Word8
    -> Array Word8
    -> m (Array Word8, Maybe (Array Word8))
breakOn :: forall (m :: * -> *).
MonadIO m =>
Word8 -> Array Word8 -> m (Array Word8, Maybe (Array Word8))
breakOn Word8
sep arr :: Array Word8
arr@(Array ByteArray#
arr# Int
off Int
len) =
    case Either Int Int
loc of
        Left Int
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return (Array Word8
arr, forall a. Maybe a
Nothing)
        Right Int
len1 -> do
            let len2 :: Int
len2 = Int
len forall a. Num a => a -> a -> a
- Int
len1 forall a. Num a => a -> a -> a
- Int
1
            forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. ByteArray# -> Int -> Int -> Array a
Array ByteArray#
arr# Int
off Int
len1, forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. ByteArray# -> Int -> Int -> Array a
Array ByteArray#
arr# (Int
off forall a. Num a => a -> a -> a
+ Int
len1 forall a. Num a => a -> a -> a
+ Int
1) Int
len2)

    where

    loc :: Either Int Int
loc = forall a b. Prim a => (b -> a -> b) -> b -> Array a -> b
foldl' forall {a}. Num a => Either a a -> Word8 -> Either a a
chk (forall a b. a -> Either a b
Left Int
0) Array Word8
arr

    chk :: Either a a -> Word8 -> Either a a
chk (Left a
i) Word8
a =
        if Word8
a forall a. Eq a => a -> a -> Bool
== Word8
sep
            then forall a b. b -> Either a b
Right a
i
            else forall a b. a -> Either a b
Left (a
i forall a. Num a => a -> a -> a
+ a
1)
    chk Either a a
r Word8
_ = Either a a
r