{-# LANGUAGE BangPatterns, CPP, MagicHash, UnboxedTuples, UnliftedFFITypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE RankNTypes #-}

-- |
-- Module      : Data.Primitive.ByteArray
-- Copyright   : (c) Roman Leshchinskiy 2009-2012
-- License     : BSD-style
--
-- Maintainer  : Roman Leshchinskiy <rl@cse.unsw.edu.au>
-- Portability : non-portable
--
-- Primitive operations on byte arrays. Most functions in this module include
-- an element type in their type signature and interpret the unit for offsets
-- and lengths as that element. A few functions (e.g. 'copyByteArray',
-- 'freezeByteArray') do not include an element type. Such functions
-- interpret offsets and lengths as units of 8-bit words.

module Data.Primitive.ByteArray (
  -- * Types
  ByteArray(..), MutableByteArray(..), ByteArray#, MutableByteArray#,

  -- * Allocation
  newByteArray, newPinnedByteArray, newAlignedPinnedByteArray,
  resizeMutableByteArray,
  shrinkMutableByteArray,

  -- * Element access
  readByteArray, writeByteArray, indexByteArray,
  -- * Char Element Access
  -- $charElementAccess
  readCharArray, writeCharArray, indexCharArray,

  -- * Constructing
  emptyByteArray,
  byteArrayFromList, byteArrayFromListN,

  -- * Folding
  foldrByteArray,

  -- * Comparing
  compareByteArrays,

  -- * Freezing and thawing
  freezeByteArray, thawByteArray, runByteArray,
  unsafeFreezeByteArray, unsafeThawByteArray,

  -- * Block operations
  copyByteArray, copyMutableByteArray,
  copyByteArrayToPtr, copyMutableByteArrayToPtr,
  copyByteArrayToAddr, copyMutableByteArrayToAddr,
  copyPtrToMutableByteArray,
  moveByteArray,
  setByteArray, fillByteArray,
  cloneByteArray, cloneMutableByteArray,

  -- * Information
  sizeofByteArray,
  sizeofMutableByteArray, getSizeofMutableByteArray, sameMutableByteArray,
#if __GLASGOW_HASKELL__ >= 802
  isByteArrayPinned, isMutableByteArrayPinned,
#endif
  byteArrayContents,
  withByteArrayContents,
  mutableByteArrayContents,
  withMutableByteArrayContents

) where

import Control.Monad.Primitive
import Control.Monad.ST
import Data.Primitive.Types
import Data.Proxy

#if MIN_VERSION_base(4,10,0)
import qualified GHC.ST as GHCST
#endif

import Foreign.C.Types
import Data.Word ( Word8 )
#if __GLASGOW_HASKELL__ >= 802
import qualified GHC.Exts as Exts
#endif
import GHC.Exts hiding (setByteArray#)

#if __GLASGOW_HASKELL__ < 804
import System.IO.Unsafe (unsafeDupablePerformIO)
#endif

import Data.Array.Byte (ByteArray(..), MutableByteArray(..))

import Data.Primitive.Internal.Operations (mutableByteArrayContentsShim)

-- | Create a new mutable byte array of the specified size in bytes.
-- The underlying memory is left uninitialized.
--
-- /Note:/ this function does not check if the input is non-negative.
newByteArray :: PrimMonad m => Int -> m (MutableByteArray (PrimState m))
{-# INLINE newByteArray #-}
newByteArray :: forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
newByteArray (I# Int#
n#)
  = forall (m :: * -> *) a.
PrimMonad m =>
(State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a
primitive (\State# (PrimState m)
s# -> case forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
newByteArray# Int#
n# State# (PrimState m)
s# of
                        (# State# (PrimState m)
s'#, MutableByteArray# (PrimState m)
arr# #) -> (# State# (PrimState m)
s'#, forall s. MutableByteArray# s -> MutableByteArray s
MutableByteArray MutableByteArray# (PrimState m)
arr# #))

-- | Create a /pinned/ byte array of the specified size in bytes. The garbage
-- collector is guaranteed not to move it. The underlying memory is left uninitialized.
--
-- /Note:/ this function does not check if the input is non-negative.
newPinnedByteArray :: PrimMonad m => Int -> m (MutableByteArray (PrimState m))
{-# INLINE newPinnedByteArray #-}
newPinnedByteArray :: forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
newPinnedByteArray (I# Int#
n#)
  = forall (m :: * -> *) a.
PrimMonad m =>
(State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a
primitive (\State# (PrimState m)
s# -> case forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
newPinnedByteArray# Int#
n# State# (PrimState m)
s# of
                        (# State# (PrimState m)
s'#, MutableByteArray# (PrimState m)
arr# #) -> (# State# (PrimState m)
s'#, forall s. MutableByteArray# s -> MutableByteArray s
MutableByteArray MutableByteArray# (PrimState m)
arr# #))

-- | Create a /pinned/ byte array of the specified size in bytes and with the
-- given alignment. The garbage collector is guaranteed not to move it.
-- The underlying memory is left uninitialized.
--
-- /Note:/ this function does not check if the input is non-negative.
newAlignedPinnedByteArray
  :: PrimMonad m
  => Int  -- ^ size
  -> Int  -- ^ alignment
  -> m (MutableByteArray (PrimState m))
{-# INLINE newAlignedPinnedByteArray #-}
newAlignedPinnedByteArray :: forall (m :: * -> *).
PrimMonad m =>
Int -> Int -> m (MutableByteArray (PrimState m))
newAlignedPinnedByteArray (I# Int#
n#) (I# Int#
k#)
  = forall (m :: * -> *) a.
PrimMonad m =>
(State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a
primitive (\State# (PrimState m)
s# -> case forall d.
Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #)
newAlignedPinnedByteArray# Int#
n# Int#
k# State# (PrimState m)
s# of
                        (# State# (PrimState m)
s'#, MutableByteArray# (PrimState m)
arr# #) -> (# State# (PrimState m)
s'#, forall s. MutableByteArray# s -> MutableByteArray s
MutableByteArray MutableByteArray# (PrimState m)
arr# #))

-- | Yield a pointer to the array's data. This operation is only safe on
-- /pinned/ byte arrays. Byte arrays allocated by 'newPinnedByteArray' and
-- 'newAlignedPinnedByteArray' are guaranteed to be pinned. Byte arrays
-- allocated by 'newByteArray' may or may not be pinned (use
-- 'isByteArrayPinned' to figure out).
--
-- Prefer 'withByteArrayContents', which ensures that the array is not
-- garbage collected while the pointer is being used.
byteArrayContents :: ByteArray -> Ptr Word8
{-# INLINE byteArrayContents #-}
byteArrayContents :: ByteArray -> Ptr Word8
byteArrayContents (ByteArray ByteArray#
arr#) = forall a. Addr# -> Ptr a
Ptr (ByteArray# -> Addr#
byteArrayContents# ByteArray#
arr#)

-- | A composition of 'byteArrayContents' and 'keepAliveUnlifted'.
-- The callback function must not return the pointer. The argument byte
-- array must be /pinned/. See 'byteArrayContents' for an explanation
-- of which byte arrays are pinned.
--
-- Note: This could be implemented with 'keepAlive' instead of
-- 'keepAliveUnlifted', but 'keepAlive' here would cause GHC to materialize
-- the wrapper data constructor on the heap.
withByteArrayContents :: PrimBase m => ByteArray -> (Ptr Word8 -> m a) -> m a
{-# INLINE withByteArrayContents #-}
withByteArrayContents :: forall (m :: * -> *) a.
PrimBase m =>
ByteArray -> (Ptr Word8 -> m a) -> m a
withByteArrayContents (ByteArray ByteArray#
arr#) Ptr Word8 -> m a
f =
  forall (m :: * -> *) (a :: UnliftedType) r.
PrimBase m =>
a -> m r -> m r
keepAliveUnlifted ByteArray#
arr# (Ptr Word8 -> m a
f (forall a. Addr# -> Ptr a
Ptr (ByteArray# -> Addr#
byteArrayContents# ByteArray#
arr#)))

-- | Yield a pointer to the array's data. This operation is only safe on
-- /pinned/ byte arrays. See 'byteArrayContents' for an explanation
-- of which byte arrays are pinned.
--
-- Prefer 'withByteArrayContents', which ensures that the array is not
-- garbage collected while the pointer is being used.
mutableByteArrayContents :: MutableByteArray s -> Ptr Word8
{-# INLINE mutableByteArrayContents #-}
mutableByteArrayContents :: forall s. MutableByteArray s -> Ptr Word8
mutableByteArrayContents (MutableByteArray MutableByteArray# s
arr#) = forall a. Addr# -> Ptr a
Ptr (forall s. MutableByteArray# s -> Addr#
mutableByteArrayContentsShim MutableByteArray# s
arr#)

-- | A composition of 'mutableByteArrayContents' and 'keepAliveUnlifted'.
-- The callback function must not return the pointer. The argument byte
-- array must be /pinned/. See 'byteArrayContents' for an explanation
-- of which byte arrays are pinned.
withMutableByteArrayContents :: PrimBase m => MutableByteArray (PrimState m) -> (Ptr Word8 -> m a) -> m a
{-# INLINE withMutableByteArrayContents #-}
withMutableByteArrayContents :: forall (m :: * -> *) a.
PrimBase m =>
MutableByteArray (PrimState m) -> (Ptr Word8 -> m a) -> m a
withMutableByteArrayContents (MutableByteArray MutableByteArray# (PrimState m)
arr#) Ptr Word8 -> m a
f =
  forall (m :: * -> *) (a :: UnliftedType) r.
PrimBase m =>
a -> m r -> m r
keepAliveUnlifted MutableByteArray# (PrimState m)
arr# (Ptr Word8 -> m a
f (forall a. Addr# -> Ptr a
Ptr (forall s. MutableByteArray# s -> Addr#
mutableByteArrayContentsShim MutableByteArray# (PrimState m)
arr#)))

-- | Check if the two arrays refer to the same memory block.
sameMutableByteArray :: MutableByteArray s -> MutableByteArray s -> Bool
{-# INLINE sameMutableByteArray #-}
sameMutableByteArray :: forall s. MutableByteArray s -> MutableByteArray s -> Bool
sameMutableByteArray (MutableByteArray MutableByteArray# s
arr#) (MutableByteArray MutableByteArray# s
brr#)
  = Int# -> Bool
isTrue# (forall d. MutableByteArray# d -> MutableByteArray# d -> Int#
sameMutableByteArray# MutableByteArray# s
arr# MutableByteArray# s
brr#)

-- | Resize a mutable byte array. The new size is given in bytes.
--
-- This will either resize the array in-place or, if not possible, allocate the
-- contents into a new, unpinned array and copy the original array's contents.
--
-- To avoid undefined behaviour, the original 'MutableByteArray' shall not be
-- accessed anymore after a 'resizeMutableByteArray' has been performed.
-- Moreover, no reference to the old one should be kept in order to allow
-- garbage collection of the original 'MutableByteArray' in case a new
-- 'MutableByteArray' had to be allocated.
--
-- @since 0.6.4.0
resizeMutableByteArray
  :: PrimMonad m => MutableByteArray (PrimState m) -> Int
                 -> m (MutableByteArray (PrimState m))
{-# INLINE resizeMutableByteArray #-}
resizeMutableByteArray :: forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> m (MutableByteArray (PrimState m))
resizeMutableByteArray (MutableByteArray MutableByteArray# (PrimState m)
arr#) (I# Int#
n#)
  = forall (m :: * -> *) a.
PrimMonad m =>
(State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a
primitive (\State# (PrimState m)
s# -> case forall d.
MutableByteArray# d
-> Int# -> State# d -> (# State# d, MutableByteArray# d #)
resizeMutableByteArray# MutableByteArray# (PrimState m)
arr# Int#
n# State# (PrimState m)
s# of
                        (# State# (PrimState m)
s'#, MutableByteArray# (PrimState m)
arr'# #) -> (# State# (PrimState m)
s'#, forall s. MutableByteArray# s -> MutableByteArray s
MutableByteArray MutableByteArray# (PrimState m)
arr'# #))

-- | Get the size of a byte array in bytes. Unlike 'sizeofMutableByteArray',
-- this function ensures sequencing in the presence of resizing.
getSizeofMutableByteArray
  :: PrimMonad m => MutableByteArray (PrimState m) -> m Int
{-# INLINE getSizeofMutableByteArray #-}
#if __GLASGOW_HASKELL__ >= 801
getSizeofMutableByteArray :: forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m Int
getSizeofMutableByteArray (MutableByteArray MutableByteArray# (PrimState m)
arr#)
  = forall (m :: * -> *) a.
PrimMonad m =>
(State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a
primitive (\State# (PrimState m)
s# -> case forall d. MutableByteArray# d -> State# d -> (# State# d, Int# #)
getSizeofMutableByteArray# MutableByteArray# (PrimState m)
arr# State# (PrimState m)
s# of
                        (# State# (PrimState m)
s'#, Int#
n# #) -> (# State# (PrimState m)
s'#, Int# -> Int
I# Int#
n# #))
#else
getSizeofMutableByteArray arr
  = return (sizeofMutableByteArray arr)
#endif

-- | Create an immutable copy of a slice of a byte array. The offset and
-- length are given in bytes.
--
-- This operation makes a copy of the specified section, so it is safe to
-- continue using the mutable array afterward.
--
-- /Note:/ The provided array should contain the full subrange
-- specified by the two Ints, but this is not checked.
freezeByteArray
  :: PrimMonad m
  => MutableByteArray (PrimState m) -- ^ source
  -> Int                            -- ^ offset in bytes
  -> Int                            -- ^ length in bytes
  -> m ByteArray
{-# INLINE freezeByteArray #-}
freezeByteArray :: forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> Int -> Int -> m ByteArray
freezeByteArray !MutableByteArray (PrimState m)
src !Int
off !Int
len = do
  MutableByteArray (PrimState m)
dst <- forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
newByteArray Int
len
  forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> MutableByteArray (PrimState m) -> Int -> Int -> m ()
copyMutableByteArray MutableByteArray (PrimState m)
dst Int
0 MutableByteArray (PrimState m)
src Int
off Int
len
  forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
unsafeFreezeByteArray MutableByteArray (PrimState m)
dst

-- | Create a mutable byte array from a slice of an immutable byte array.
-- The offset and length are given in bytes.
--
-- This operation makes a copy of the specified slice, so it is safe to
-- use the immutable array afterward.
--
-- /Note:/ The provided array should contain the full subrange
-- specified by the two Ints, but this is not checked.
--
-- @since 0.7.2.0
thawByteArray
  :: PrimMonad m
  => ByteArray -- ^ source
  -> Int       -- ^ offset in bytes
  -> Int       -- ^ length in bytes
  -> m (MutableByteArray (PrimState m))
{-# INLINE thawByteArray #-}
thawByteArray :: forall (m :: * -> *).
PrimMonad m =>
ByteArray -> Int -> Int -> m (MutableByteArray (PrimState m))
thawByteArray !ByteArray
src !Int
off !Int
len = do
  MutableByteArray (PrimState m)
dst <- forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
newByteArray Int
len
  forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> ByteArray -> Int -> Int -> m ()
copyByteArray MutableByteArray (PrimState m)
dst Int
0 ByteArray
src Int
off Int
len
  forall (m :: * -> *) a. Monad m => a -> m a
return MutableByteArray (PrimState m)
dst

-- | Convert a mutable byte array to an immutable one without copying. The
-- array should not be modified after the conversion.
unsafeFreezeByteArray
  :: PrimMonad m => MutableByteArray (PrimState m) -> m ByteArray
{-# INLINE unsafeFreezeByteArray #-}
unsafeFreezeByteArray :: forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
unsafeFreezeByteArray (MutableByteArray MutableByteArray# (PrimState m)
arr#)
  = forall (m :: * -> *) a.
PrimMonad m =>
(State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a
primitive (\State# (PrimState m)
s# -> case forall d.
MutableByteArray# d -> State# d -> (# State# d, ByteArray# #)
unsafeFreezeByteArray# MutableByteArray# (PrimState m)
arr# State# (PrimState m)
s# of
                        (# State# (PrimState m)
s'#, ByteArray#
arr'# #) -> (# State# (PrimState m)
s'#, ByteArray# -> ByteArray
ByteArray ByteArray#
arr'# #))

-- | Convert an immutable byte array to a mutable one without copying. The
-- original array should not be used after the conversion.
unsafeThawByteArray
  :: PrimMonad m => ByteArray -> m (MutableByteArray (PrimState m))
{-# INLINE unsafeThawByteArray #-}
unsafeThawByteArray :: forall (m :: * -> *).
PrimMonad m =>
ByteArray -> m (MutableByteArray (PrimState m))
unsafeThawByteArray (ByteArray ByteArray#
arr#)
  = forall (m :: * -> *) a.
PrimMonad m =>
(State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a
primitive (\State# (PrimState m)
s# -> (# State# (PrimState m)
s#, forall s. MutableByteArray# s -> MutableByteArray s
MutableByteArray (unsafeCoerce# :: forall a b. a -> b
unsafeCoerce# ByteArray#
arr#) #))

-- | Size of the byte array in bytes.
sizeofByteArray :: ByteArray -> Int
{-# INLINE sizeofByteArray #-}
sizeofByteArray :: ByteArray -> Int
sizeofByteArray (ByteArray ByteArray#
arr#) = Int# -> Int
I# (ByteArray# -> Int#
sizeofByteArray# ByteArray#
arr#)

-- | Size of the mutable byte array in bytes.
--
-- This function is deprecated and will be removed. Its behavior
-- is undefined if 'resizeMutableByteArray' is ever called on the mutable
-- byte array given as the argument. Prefer 'getSizeofMutableByteArray',
-- which ensures correct sequencing in the presence of resizing.
sizeofMutableByteArray :: MutableByteArray s -> Int
{-# INLINE sizeofMutableByteArray #-}
{-# DEPRECATED sizeofMutableByteArray "use getSizeofMutableByteArray instead" #-}
sizeofMutableByteArray :: forall s. MutableByteArray s -> Int
sizeofMutableByteArray (MutableByteArray MutableByteArray# s
arr#) = Int# -> Int
I# (forall d. MutableByteArray# d -> Int#
sizeofMutableByteArray# MutableByteArray# s
arr#)

-- | Shrink a mutable byte array. The new size is given in bytes.
-- It must be smaller than the old size. The array will be resized in place.
--
-- @since 0.7.1.0
shrinkMutableByteArray :: PrimMonad m
  => MutableByteArray (PrimState m)
  -> Int -- ^ new size
  -> m ()
{-# INLINE shrinkMutableByteArray #-}
shrinkMutableByteArray :: forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> Int -> m ()
shrinkMutableByteArray (MutableByteArray MutableByteArray# (PrimState m)
arr#) (I# Int#
n#)
  = forall (m :: * -> *).
PrimMonad m =>
(State# (PrimState m) -> State# (PrimState m)) -> m ()
primitive_ (forall d. MutableByteArray# d -> Int# -> State# d -> State# d
shrinkMutableByteArray# MutableByteArray# (PrimState m)
arr# Int#
n#)

#if __GLASGOW_HASKELL__ >= 802
-- | Check whether or not the byte array is pinned. Pinned byte arrays cannot
-- be moved by the garbage collector. It is safe to use 'byteArrayContents' on
-- such byte arrays.
--
-- Caution: This function is only available when compiling with GHC 8.2 or
-- newer.
--
-- @since 0.6.4.0
isByteArrayPinned :: ByteArray -> Bool
{-# INLINE isByteArrayPinned #-}
isByteArrayPinned :: ByteArray -> Bool
isByteArrayPinned (ByteArray ByteArray#
arr#) = Int# -> Bool
isTrue# (ByteArray# -> Int#
Exts.isByteArrayPinned# ByteArray#
arr#)

-- | Check whether or not the mutable byte array is pinned.
--
-- Caution: This function is only available when compiling with GHC 8.2 or
-- newer.
--
-- @since 0.6.4.0
isMutableByteArrayPinned :: MutableByteArray s -> Bool
{-# INLINE isMutableByteArrayPinned #-}
isMutableByteArrayPinned :: forall s. MutableByteArray s -> Bool
isMutableByteArrayPinned (MutableByteArray MutableByteArray# s
marr#) = Int# -> Bool
isTrue# (forall d. MutableByteArray# d -> Int#
Exts.isMutableByteArrayPinned# MutableByteArray# s
marr#)
#endif

-- | Read a primitive value from the byte array. The offset is given in
-- elements of type @a@ rather than in bytes.
--
-- /Note:/ this function does not do bounds checking.
indexByteArray :: Prim a => ByteArray -> Int -> a
{-# INLINE indexByteArray #-}
indexByteArray :: forall a. Prim a => ByteArray -> Int -> a
indexByteArray (ByteArray ByteArray#
arr#) (I# Int#
i#) = forall a. Prim a => ByteArray# -> Int# -> a
indexByteArray# ByteArray#
arr# Int#
i#

-- | Read a primitive value from the byte array. The offset is given in
-- elements of type @a@ rather than in bytes.
--
-- /Note:/ this function does not do bounds checking.
readByteArray
  :: (Prim a, PrimMonad m) => MutableByteArray (PrimState m) -> Int -> m a
{-# INLINE readByteArray #-}
readByteArray :: forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> m a
readByteArray (MutableByteArray MutableByteArray# (PrimState m)
arr#) (I# Int#
i#)
  = forall (m :: * -> *) a.
PrimMonad m =>
(State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a
primitive (forall a s.
Prim a =>
MutableByteArray# s -> Int# -> State# s -> (# State# s, a #)
readByteArray# MutableByteArray# (PrimState m)
arr# Int#
i#)

-- | Write a primitive value to the byte array. The offset is given in
-- elements of type @a@ rather than in bytes.
--
-- /Note:/ this function does not do bounds checking.
writeByteArray
  :: (Prim a, PrimMonad m) => MutableByteArray (PrimState m) -> Int -> a -> m ()
{-# INLINE writeByteArray #-}
writeByteArray :: forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
writeByteArray (MutableByteArray MutableByteArray# (PrimState m)
arr#) (I# Int#
i#) a
x
  = forall (m :: * -> *).
PrimMonad m =>
(State# (PrimState m) -> State# (PrimState m)) -> m ()
primitive_ (forall a s.
Prim a =>
MutableByteArray# s -> Int# -> a -> State# s -> State# s
writeByteArray# MutableByteArray# (PrimState m)
arr# Int#
i# a
x)

-- | Right-fold over the elements of a 'ByteArray'.
foldrByteArray :: forall a b. (Prim a) => (a -> b -> b) -> b -> ByteArray -> b
{-# INLINE foldrByteArray #-}
foldrByteArray :: forall a b. Prim a => (a -> b -> b) -> b -> ByteArray -> b
foldrByteArray a -> b -> b
f b
z ByteArray
arr = Int -> b
go Int
0
  where
    go :: Int -> b
go Int
i
      | Int
i forall a. Ord a => a -> a -> Bool
< Int
maxI  = a -> b -> b
f (forall a. Prim a => ByteArray -> Int -> a
indexByteArray ByteArray
arr Int
i) (Int -> b
go (Int
i forall a. Num a => a -> a -> a
+ Int
1))
      | Bool
otherwise = b
z
    maxI :: Int
maxI = ByteArray -> Int
sizeofByteArray ByteArray
arr forall a. Integral a => a -> a -> a
`quot` forall a. Prim a => Int
sizeOfType @a

-- | Create a 'ByteArray' from a list.
--
-- @byteArrayFromList xs = `byteArrayFromListN` (length xs) xs@
byteArrayFromList :: Prim a => [a] -> ByteArray
byteArrayFromList :: forall a. Prim a => [a] -> ByteArray
byteArrayFromList [a]
xs = forall a. Prim a => Int -> [a] -> ByteArray
byteArrayFromListN (forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
xs) [a]
xs

-- | Create a 'ByteArray' from a list of a known length. If the length
-- of the list does not match the given length, this throws an exception.
byteArrayFromListN :: forall a. Prim a => Int -> [a] -> ByteArray
byteArrayFromListN :: forall a. Prim a => Int -> [a] -> ByteArray
byteArrayFromListN Int
n [a]
ys = forall a. (forall s. ST s a) -> a
runST forall a b. (a -> b) -> a -> b
$ do
    MutableByteArray s
marr <- forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
newByteArray (Int
n forall a. Num a => a -> a -> a
* forall a. Prim a => Int
sizeOfType @a)
    let go :: Int -> [a] -> ST s ()
go !Int
ix [] = if Int
ix forall a. Eq a => a -> a -> Bool
== Int
n
          then forall (m :: * -> *) a. Monad m => a -> m a
return ()
          else forall a. String -> String -> a
die String
"byteArrayFromListN" String
"list length less than specified size"
        go !Int
ix (a
x : [a]
xs) = if Int
ix forall a. Ord a => a -> a -> Bool
< Int
n
          then do
            forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
writeByteArray MutableByteArray s
marr Int
ix a
x
            Int -> [a] -> ST s ()
go (Int
ix forall a. Num a => a -> a -> a
+ Int
1) [a]
xs
          else forall a. String -> String -> a
die String
"byteArrayFromListN" String
"list length greater than specified size"
    Int -> [a] -> ST s ()
go Int
0 [a]
ys
    forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
unsafeFreezeByteArray MutableByteArray s
marr

unI# :: Int -> Int#
unI# :: Int -> Int#
unI# (I# Int#
n#) = Int#
n#

-- | Copy a slice of an immutable byte array to a mutable byte array.
--
-- /Note:/ this function does not do bounds or overlap checking.
copyByteArray
  :: PrimMonad m
  => MutableByteArray (PrimState m) -- ^ destination array
  -> Int                            -- ^ offset into destination array
  -> ByteArray                      -- ^ source array
  -> Int                            -- ^ offset into source array
  -> Int                            -- ^ number of bytes to copy
  -> m ()
{-# INLINE copyByteArray #-}
copyByteArray :: forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> ByteArray -> Int -> Int -> m ()
copyByteArray (MutableByteArray MutableByteArray# (PrimState m)
dst#) Int
doff (ByteArray ByteArray#
src#) Int
soff Int
sz
  = forall (m :: * -> *).
PrimMonad m =>
(State# (PrimState m) -> State# (PrimState m)) -> m ()
primitive_ (forall d.
ByteArray#
-> Int#
-> MutableByteArray# d
-> Int#
-> Int#
-> State# d
-> State# d
copyByteArray# ByteArray#
src# (Int -> Int#
unI# Int
soff) MutableByteArray# (PrimState m)
dst# (Int -> Int#
unI# Int
doff) (Int -> Int#
unI# Int
sz))

-- | Copy a slice of a mutable byte array into another array. The two slices
-- may not overlap.
--
-- /Note:/ this function does not do bounds or overlap checking.
copyMutableByteArray
  :: PrimMonad m
  => MutableByteArray (PrimState m) -- ^ destination array
  -> Int                            -- ^ offset into destination array
  -> MutableByteArray (PrimState m) -- ^ source array
  -> Int                            -- ^ offset into source array
  -> Int                            -- ^ number of bytes to copy
  -> m ()
{-# INLINE copyMutableByteArray #-}
copyMutableByteArray :: forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> MutableByteArray (PrimState m) -> Int -> Int -> m ()
copyMutableByteArray (MutableByteArray MutableByteArray# (PrimState m)
dst#) Int
doff
                     (MutableByteArray MutableByteArray# (PrimState m)
src#) Int
soff Int
sz
  = forall (m :: * -> *).
PrimMonad m =>
(State# (PrimState m) -> State# (PrimState m)) -> m ()
primitive_ (forall d.
MutableByteArray# d
-> Int#
-> MutableByteArray# d
-> Int#
-> Int#
-> State# d
-> State# d
copyMutableByteArray# MutableByteArray# (PrimState m)
src# (Int -> Int#
unI# Int
soff) MutableByteArray# (PrimState m)
dst# (Int -> Int#
unI# Int
doff) (Int -> Int#
unI# Int
sz))

-- | Copy a slice of a byte array to an unmanaged pointer address. These must not
-- overlap. The offset and length are given in elements, not in bytes.
--
-- /Note:/ this function does not do bounds or overlap checking.
--
-- @since 0.7.1.0
copyByteArrayToPtr
  :: forall m a. (PrimMonad m, Prim a)
  => Ptr a -- ^ destination
  -> ByteArray -- ^ source array
  -> Int -- ^ offset into source array, interpreted as elements of type @a@
  -> Int -- ^ number of elements to copy
  -> m ()
{-# INLINE copyByteArrayToPtr #-}
copyByteArrayToPtr :: forall (m :: * -> *) a.
(PrimMonad m, Prim a) =>
Ptr a -> ByteArray -> Int -> Int -> m ()
copyByteArrayToPtr (Ptr Addr#
dst#) (ByteArray ByteArray#
src#) Int
soff Int
sz
  = forall (m :: * -> *).
PrimMonad m =>
(State# (PrimState m) -> State# (PrimState m)) -> m ()
primitive_ (forall d.
ByteArray# -> Int# -> Addr# -> Int# -> State# d -> State# d
copyByteArrayToAddr# ByteArray#
src# (Int -> Int#
unI# Int
soff Int# -> Int# -> Int#
*# Int#
siz#) Addr#
dst# (Int -> Int#
unI# Int
sz Int# -> Int# -> Int#
*# Int#
siz#))
  where
  siz# :: Int#
siz# = forall a. Prim a => Proxy a -> Int#
sizeOfType# (forall {k} (t :: k). Proxy t
Proxy :: Proxy a)

-- | Copy from an unmanaged pointer address to a byte array. These must not
-- overlap. The offset and length are given in elements, not in bytes.
--
-- /Note:/ this function does not do bounds or overlap checking.
copyPtrToMutableByteArray :: forall m a. (PrimMonad m, Prim a)
  => MutableByteArray (PrimState m) -- ^ destination array
  -> Int   -- ^ destination offset given in elements of type @a@
  -> Ptr a -- ^ source pointer
  -> Int   -- ^ number of elements
  -> m ()
{-# INLINE copyPtrToMutableByteArray #-}
copyPtrToMutableByteArray :: forall (m :: * -> *) a.
(PrimMonad m, Prim a) =>
MutableByteArray (PrimState m) -> Int -> Ptr a -> Int -> m ()
copyPtrToMutableByteArray (MutableByteArray MutableByteArray# (PrimState m)
ba#) (I# Int#
doff#) (Ptr Addr#
addr#) (I# Int#
n#) =
  forall (m :: * -> *).
PrimMonad m =>
(State# (PrimState m) -> State# (PrimState m)) -> m ()
primitive_ (forall d.
Addr#
-> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
copyAddrToByteArray# Addr#
addr# MutableByteArray# (PrimState m)
ba# (Int#
doff# Int# -> Int# -> Int#
*# Int#
siz#) (Int#
n# Int# -> Int# -> Int#
*# Int#
siz#))
  where
  siz# :: Int#
siz# = forall a. Prim a => Proxy a -> Int#
sizeOfType# (forall {k} (t :: k). Proxy t
Proxy :: Proxy a)


-- | Copy a slice of a mutable byte array to an unmanaged pointer address.
-- These must not overlap. The offset and length are given in elements, not
-- in bytes.
--
-- /Note:/ this function does not do bounds or overlap checking.
--
-- @since 0.7.1.0
copyMutableByteArrayToPtr
  :: forall m a. (PrimMonad m, Prim a)
  => Ptr a -- ^ destination
  -> MutableByteArray (PrimState m) -- ^ source array
  -> Int -- ^ offset into source array, interpreted as elements of type @a@
  -> Int -- ^ number of elements to copy
  -> m ()
{-# INLINE copyMutableByteArrayToPtr #-}
copyMutableByteArrayToPtr :: forall (m :: * -> *) a.
(PrimMonad m, Prim a) =>
Ptr a -> MutableByteArray (PrimState m) -> Int -> Int -> m ()
copyMutableByteArrayToPtr (Ptr Addr#
dst#) (MutableByteArray MutableByteArray# (PrimState m)
src#) Int
soff Int
sz
  = forall (m :: * -> *).
PrimMonad m =>
(State# (PrimState m) -> State# (PrimState m)) -> m ()
primitive_ (forall d.
MutableByteArray# d
-> Int# -> Addr# -> Int# -> State# d -> State# d
copyMutableByteArrayToAddr# MutableByteArray# (PrimState m)
src# (Int -> Int#
unI# Int
soff Int# -> Int# -> Int#
*# Int#
siz#) Addr#
dst# (Int -> Int#
unI# Int
sz Int# -> Int# -> Int#
*# Int#
siz#))
  where
  siz# :: Int#
siz# = forall a. Prim a => Proxy a -> Int#
sizeOfType# (forall {k} (t :: k). Proxy t
Proxy :: Proxy a)

------
--- These latter two should be DEPRECATED
-----

-- | Copy a slice of a byte array to an unmanaged address. These must not
-- overlap.
--
-- Note: This function is just 'copyByteArrayToPtr' where @a@ is 'Word8'.
--
-- @since 0.6.4.0
copyByteArrayToAddr
  :: PrimMonad m
  => Ptr Word8 -- ^ destination
  -> ByteArray -- ^ source array
  -> Int -- ^ offset into source array
  -> Int -- ^ number of bytes to copy
  -> m ()
{-# INLINE copyByteArrayToAddr #-}
copyByteArrayToAddr :: forall (m :: * -> *).
PrimMonad m =>
Ptr Word8 -> ByteArray -> Int -> Int -> m ()
copyByteArrayToAddr (Ptr Addr#
dst#) (ByteArray ByteArray#
src#) Int
soff Int
sz
  = forall (m :: * -> *).
PrimMonad m =>
(State# (PrimState m) -> State# (PrimState m)) -> m ()
primitive_ (forall d.
ByteArray# -> Int# -> Addr# -> Int# -> State# d -> State# d
copyByteArrayToAddr# ByteArray#
src# (Int -> Int#
unI# Int
soff) Addr#
dst# (Int -> Int#
unI# Int
sz))

-- | Copy a slice of a mutable byte array to an unmanaged address. These must
-- not overlap.
--
-- Note: This function is just 'copyMutableByteArrayToPtr' where @a@ is 'Word8'.
--
-- @since 0.6.4.0
copyMutableByteArrayToAddr
  :: PrimMonad m
  => Ptr Word8 -- ^ destination
  -> MutableByteArray (PrimState m) -- ^ source array
  -> Int -- ^ offset into source array
  -> Int -- ^ number of bytes to copy
  -> m ()
{-# INLINE copyMutableByteArrayToAddr #-}
copyMutableByteArrayToAddr :: forall (m :: * -> *).
PrimMonad m =>
Ptr Word8 -> MutableByteArray (PrimState m) -> Int -> Int -> m ()
copyMutableByteArrayToAddr (Ptr Addr#
dst#) (MutableByteArray MutableByteArray# (PrimState m)
src#) Int
soff Int
sz
  = forall (m :: * -> *).
PrimMonad m =>
(State# (PrimState m) -> State# (PrimState m)) -> m ()
primitive_ (forall d.
MutableByteArray# d
-> Int# -> Addr# -> Int# -> State# d -> State# d
copyMutableByteArrayToAddr# MutableByteArray# (PrimState m)
src# (Int -> Int#
unI# Int
soff) Addr#
dst# (Int -> Int#
unI# Int
sz))

-- | Copy a slice of a mutable byte array into another, potentially
-- overlapping array.
moveByteArray
  :: PrimMonad m
  => MutableByteArray (PrimState m) -- ^ destination array
  -> Int                            -- ^ offset into destination array
  -> MutableByteArray (PrimState m) -- ^ source array
  -> Int                            -- ^ offset into source array
  -> Int                            -- ^ number of bytes to copy
  -> m ()
{-# INLINE moveByteArray #-}
moveByteArray :: forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> MutableByteArray (PrimState m) -> Int -> Int -> m ()
moveByteArray (MutableByteArray MutableByteArray# (PrimState m)
dst#) Int
doff
              (MutableByteArray MutableByteArray# (PrimState m)
src#) Int
soff Int
sz
  = forall (m1 :: * -> *) (m2 :: * -> *) a.
(PrimBase m1, PrimMonad m2) =>
m1 a -> m2 a
unsafePrimToPrim
  forall a b. (a -> b) -> a -> b
$ forall s.
MutableByteArray# s
-> CPtrdiff -> MutableByteArray# s -> CPtrdiff -> CSize -> IO ()
memmove_mba MutableByteArray# (PrimState m)
dst# (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
doff) MutableByteArray# (PrimState m)
src# (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
soff)
                     (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
sz)

-- | Fill a slice of a mutable byte array with a value. The offset and length
-- are given in elements of type @a@ rather than in bytes.
--
-- /Note:/ this function does not do bounds checking.
setByteArray
  :: (Prim a, PrimMonad m)
  => MutableByteArray (PrimState m) -- ^ array to fill
  -> Int                            -- ^ offset into array
  -> Int                            -- ^ number of values to fill
  -> a                              -- ^ value to fill with
  -> m ()
{-# INLINE setByteArray #-}
setByteArray :: forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> Int -> a -> m ()
setByteArray (MutableByteArray MutableByteArray# (PrimState m)
dst#) (I# Int#
doff#) (I# Int#
sz#) a
x
  = forall (m :: * -> *).
PrimMonad m =>
(State# (PrimState m) -> State# (PrimState m)) -> m ()
primitive_ (forall a s.
Prim a =>
MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s
setByteArray# MutableByteArray# (PrimState m)
dst# Int#
doff# Int#
sz# a
x)

-- | Fill a slice of a mutable byte array with a byte.
--
-- /Note:/ this function does not do bounds checking.
fillByteArray
  :: PrimMonad m
  => MutableByteArray (PrimState m) -- ^ array to fill
  -> Int                            -- ^ offset into array
  -> Int                            -- ^ number of bytes to fill
  -> Word8                          -- ^ byte to fill with
  -> m ()
{-# INLINE fillByteArray #-}
fillByteArray :: forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> Int -> Int -> Word8 -> m ()
fillByteArray = forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> Int -> a -> m ()
setByteArray

foreign import ccall unsafe "primitive-memops.h hsprimitive_memmove"
  memmove_mba :: MutableByteArray# s -> CPtrdiff
              -> MutableByteArray# s -> CPtrdiff
              -> CSize -> IO ()

-- | Lexicographic comparison of equal-length slices into two byte arrays.
-- This wraps the @compareByteArrays#@ primop, which wraps @memcmp@.
compareByteArrays
  :: ByteArray -- ^ array A
  -> Int       -- ^ offset A, given in bytes
  -> ByteArray -- ^ array B
  -> Int       -- ^ offset B, given in bytes
  -> Int       -- ^ length of the slice, given in bytes
  -> Ordering
{-# INLINE compareByteArrays #-}
#if __GLASGOW_HASKELL__ >= 804
compareByteArrays :: ByteArray -> Int -> ByteArray -> Int -> Int -> Ordering
compareByteArrays (ByteArray ByteArray#
ba1#) (I# Int#
off1#) (ByteArray ByteArray#
ba2#) (I# Int#
off2#) (I# Int#
n#)
  = forall a. Ord a => a -> a -> Ordering
compare (Int# -> Int
I# (ByteArray# -> Int# -> ByteArray# -> Int# -> Int# -> Int#
compareByteArrays# ByteArray#
ba1# Int#
off1# ByteArray#
ba2# Int#
off2# Int#
n#)) Int
0
#else
-- Emulate GHC 8.4's 'GHC.Prim.compareByteArrays#'
compareByteArrays (ByteArray ba1#) (I# off1#) (ByteArray ba2#) (I# off2#) (I# n#)
  = compare (fromCInt (unsafeDupablePerformIO (memcmp_ba_offs ba1# off1# ba2# off2# n))) 0
  where
    n = fromIntegral (I# n#) :: CSize
    fromCInt = fromIntegral :: CInt -> Int

foreign import ccall unsafe "primitive-memops.h hsprimitive_memcmp_offset"
  memcmp_ba_offs :: ByteArray# -> Int# -> ByteArray# -> Int# -> CSize -> IO CInt
#endif

-- | The empty 'ByteArray'.
emptyByteArray :: ByteArray
{-# NOINLINE emptyByteArray #-}
emptyByteArray :: ByteArray
emptyByteArray = forall a. (forall s. ST s a) -> a
runST (forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
newByteArray Int
0 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
unsafeFreezeByteArray)

die :: String -> String -> a
die :: forall a. String -> String -> a
die String
fun String
problem = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"Data.Primitive.ByteArray." forall a. [a] -> [a] -> [a]
++ String
fun forall a. [a] -> [a] -> [a]
++ String
": " forall a. [a] -> [a] -> [a]
++ String
problem

-- | Return a newly allocated array with the specified subrange of the
-- provided array. The provided array should contain the full subrange
-- specified by the two Ints, but this is not checked.
cloneByteArray
  :: ByteArray -- ^ source array
  -> Int       -- ^ offset into destination array
  -> Int       -- ^ number of bytes to copy
  -> ByteArray
{-# INLINE cloneByteArray #-}
cloneByteArray :: ByteArray -> Int -> Int -> ByteArray
cloneByteArray ByteArray
src Int
off Int
n = (forall s. ST s (MutableByteArray s)) -> ByteArray
runByteArray forall a b. (a -> b) -> a -> b
$ do
  MutableByteArray s
dst <- forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
newByteArray Int
n
  forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> ByteArray -> Int -> Int -> m ()
copyByteArray MutableByteArray s
dst Int
0 ByteArray
src Int
off Int
n
  forall (m :: * -> *) a. Monad m => a -> m a
return MutableByteArray s
dst

-- | Return a newly allocated mutable array with the specified subrange of
-- the provided mutable array. The provided mutable array should contain the
-- full subrange specified by the two Ints, but this is not checked.
cloneMutableByteArray :: PrimMonad m
  => MutableByteArray (PrimState m) -- ^ source array
  -> Int -- ^ offset into destination array
  -> Int -- ^ number of bytes to copy
  -> m (MutableByteArray (PrimState m))
{-# INLINE cloneMutableByteArray #-}
cloneMutableByteArray :: forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> Int -> m (MutableByteArray (PrimState m))
cloneMutableByteArray MutableByteArray (PrimState m)
src Int
off Int
n = do
  MutableByteArray (PrimState m)
dst <- forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
newByteArray Int
n
  forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> MutableByteArray (PrimState m) -> Int -> Int -> m ()
copyMutableByteArray MutableByteArray (PrimState m)
dst Int
0 MutableByteArray (PrimState m)
src Int
off Int
n
  forall (m :: * -> *) a. Monad m => a -> m a
return MutableByteArray (PrimState m)
dst

-- | Execute the monadic action and freeze the resulting array.
--
-- > runByteArray m = runST $ m >>= unsafeFreezeByteArray
runByteArray
  :: (forall s. ST s (MutableByteArray s))
  -> ByteArray
#if MIN_VERSION_base(4,10,0) /* In new GHCs, runRW# is available. */
runByteArray :: (forall s. ST s (MutableByteArray s)) -> ByteArray
runByteArray forall s. ST s (MutableByteArray s)
m = ByteArray# -> ByteArray
ByteArray ((forall s. ST s (MutableByteArray s)) -> ByteArray#
runByteArray# forall s. ST s (MutableByteArray s)
m)

runByteArray#
  :: (forall s. ST s (MutableByteArray s))
  -> ByteArray#
runByteArray# :: (forall s. ST s (MutableByteArray s)) -> ByteArray#
runByteArray# forall s. ST s (MutableByteArray s)
m = case forall o. (State# RealWorld -> o) -> o
runRW# forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s ->
  case forall s a. ST s a -> State# s -> (# State# s, a #)
unST forall s. ST s (MutableByteArray s)
m State# RealWorld
s of { (# State# RealWorld
s', MutableByteArray MutableByteArray# RealWorld
mary# #) ->
  forall d.
MutableByteArray# d -> State# d -> (# State# d, ByteArray# #)
unsafeFreezeByteArray# MutableByteArray# RealWorld
mary# State# RealWorld
s'} of (# State# RealWorld
_, ByteArray#
ary# #) -> ByteArray#
ary#

unST :: ST s a -> State# s -> (# State# s, a #)
unST :: forall s a. ST s a -> State# s -> (# State# s, a #)
unST (GHCST.ST STRep s a
f) = STRep s a
f
#else /* In older GHCs, runRW# is not available. */
runByteArray m = runST $ m >>= unsafeFreezeByteArray
#endif

{- $charElementAccess
GHC provides two sets of element accessors for 'Char'. One set faithfully
represents 'Char' as 32-bit words using UTF-32. The other set represents
'Char' as 8-bit words using Latin-1 (ISO-8859-1), and the write operation
has undefined behavior for codepoints outside of the ASCII and Latin-1
blocks. The 'Prim' instance for 'Char' uses the UTF-32 set of operators.
-}

-- | Read an 8-bit element from the byte array, interpreting it as a
-- Latin-1-encoded character. The offset is given in bytes.
--
-- /Note:/ this function does not do bounds checking.
readCharArray :: PrimMonad m => MutableByteArray (PrimState m) -> Int -> m Char
{-# INLINE readCharArray #-}
readCharArray :: forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> Int -> m Char
readCharArray (MutableByteArray MutableByteArray# (PrimState m)
arr#) (I# Int#
i#) = forall (m :: * -> *) a.
PrimMonad m =>
(State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a
primitive
  (\State# (PrimState m)
s0 -> case forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #)
readCharArray# MutableByteArray# (PrimState m)
arr# Int#
i# State# (PrimState m)
s0 of
    (# State# (PrimState m)
s1, Char#
c #) -> (# State# (PrimState m)
s1, Char# -> Char
C# Char#
c #)
  )

-- | Write a character to the byte array, encoding it with Latin-1 as
-- a single byte. Behavior is undefined for codepoints outside of the
-- ASCII and Latin-1 blocks. The offset is given in bytes.
--
-- /Note:/ this function does not do bounds checking.
writeCharArray
  :: PrimMonad m => MutableByteArray (PrimState m) -> Int -> Char -> m ()
{-# INLINE writeCharArray #-}
writeCharArray :: forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> Int -> Char -> m ()
writeCharArray (MutableByteArray MutableByteArray# (PrimState m)
arr#) (I# Int#
i#) (C# Char#
c)
  = forall (m :: * -> *).
PrimMonad m =>
(State# (PrimState m) -> State# (PrimState m)) -> m ()
primitive_ (forall d.
MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
writeCharArray# MutableByteArray# (PrimState m)
arr# Int#
i# Char#
c)

-- | Read an 8-bit element from the byte array, interpreting it as a
-- Latin-1-encoded character. The offset is given in bytes.
--
-- /Note:/ this function does not do bounds checking.
indexCharArray :: ByteArray -> Int -> Char
{-# INLINE indexCharArray #-}
indexCharArray :: ByteArray -> Int -> Char
indexCharArray (ByteArray ByteArray#
arr#) (I# Int#
i#) = Char# -> Char
C# (ByteArray# -> Int# -> Char#
indexCharArray# ByteArray#
arr# Int#
i#)