{-# LANGUAGE UnboxedTuples #-}

#include "inline.hs"

-- |
-- Module      : Streamly.Internal.Data.Array.Prim.Pinned.Type
-- Copyright   : (c) 2020 Composewell Technologies
--
-- License     : BSD-3-Clause
-- Maintainer  : streamly@composewell.com
-- Stability   : experimental
-- Portability : GHC
--
module Streamly.Internal.Data.Array.Prim.Pinned.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

    , toPtr

    , touchArray
    , withArrayAsPtr
    )
where

import Foreign.C.Types (CSize(..))
import GHC.IO (IO(..))
import Foreign.Ptr (minusPtr, nullPtr, plusPtr)

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

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

-------------------------------------------------------------------------------
-- Utility functions
-------------------------------------------------------------------------------

foreign import ccall unsafe "string.h memchr" c_memchr
    :: Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8)

-------------------------------------------------------------------------------
-- Using as a Pointer
-------------------------------------------------------------------------------

-- Change name later.
{-# INLINE toPtr #-}
toPtr :: Array a -> Ptr a
toPtr :: forall a. Array a -> Ptr a
toPtr (Array ByteArray#
arr# Int
off Int
_) = forall a. Addr# -> Ptr a
Ptr (ByteArray# -> Addr#
byteArrayContents# ByteArray#
arr#) forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
off

{-# INLINE touchArray #-}
touchArray :: Array a -> IO ()
touchArray :: forall a. Array a -> IO ()
touchArray (Array ByteArray#
arr# Int
_ Int
_) = forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s -> case touch# :: forall a. a -> State# RealWorld -> State# RealWorld
touch# ByteArray#
arr# State# RealWorld
s of State# RealWorld
s1 -> (# State# RealWorld
s1, () #)

{-# INLINE withArrayAsPtr #-}
withArrayAsPtr :: Array a -> (Ptr a -> IO b) -> IO b
withArrayAsPtr :: forall a b. Array a -> (Ptr a -> IO b) -> IO b
withArrayAsPtr Array a
arr Ptr a -> IO b
f = do
    b
r <- Ptr a -> IO b
f (forall a. Array a -> Ptr a
toPtr Array a
arr)
    forall a. Array a -> IO ()
touchArray Array a
arr
    forall (m :: * -> *) a. Monad m => a -> m a
return b
r

-- Drops the separator byte
{-# 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) = do
    let p :: Ptr Word8
p = forall a. Array a -> Ptr a
toPtr Array Word8
arr
        loc :: Ptr Word8
loc = forall a. IO a -> a
unsafePerformIO forall a b. (a -> b) -> a -> b
$ Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8)
c_memchr Ptr Word8
p Word8
sep (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Prim a => Array a -> Int
byteLength Array Word8
arr))
        len1 :: Int
len1 = Ptr Word8
loc forall a b. Ptr a -> Ptr b -> Int
`minusPtr` Ptr Word8
p
        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 b. (a -> b) -> a -> b
$
        if Ptr Word8
loc forall a. Eq a => a -> a -> Bool
== forall a. Ptr a
nullPtr
        then (Array Word8
arr, forall a. Maybe a
Nothing)
        else ( 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)