{-# language BangPatterns #-}
{-# language MagicHash #-}
{-# language RankNTypes #-}
{-# language ScopedTypeVariables #-}
{-# language KindSignatures #-}
module PrimVector
( unsafeCloneFromByteArray
) where
import Arithmetic.Types (Nat#)
import Control.Monad.ST (runST)
import Data.Primitive (ByteArray(ByteArray))
import Data.Unlifted (PrimArray#(PrimArray#))
import GHC.Exts (TYPE)
import GHC.Int (Int(I#))
import GHC.TypeNats (Nat)
import Rep (R)
import Vector (Vector)
import qualified Arithmetic.Nat as Nat
import qualified Data.Primitive as PM
import qualified Vector as V
import qualified Element as E
unsafeCloneFromByteArray :: forall (n :: Nat) (a :: TYPE R).
Int
-> Nat# n
-> ByteArray
-> Vector n a
unsafeCloneFromByteArray :: forall (n :: Nat) (a :: TYPE R).
Int -> Nat# n -> ByteArray -> Vector n a
unsafeCloneFromByteArray !Int
ix !Nat# n
n !ByteArray
b
| Int
ix Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 = [Char] -> Vector n a
forall a. [Char] -> a
errorWithoutStackTrace [Char]
"PrimVector.cloneFromByteArray: negative offset"
| Int
ixScaled Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
nScaled Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
sz = [Char] -> Vector n a
forall a. [Char] -> a
errorWithoutStackTrace [Char]
"PrimVector.cloneFromByteArray: slice goes past the end"
| Bool
otherwise =
let !(ByteArray ByteArray#
result) = (forall s. ST s ByteArray) -> ByteArray
forall a. (forall s. ST s a) -> a
runST ((forall s. ST s ByteArray) -> ByteArray)
-> (forall s. ST s ByteArray) -> ByteArray
forall a b. (a -> b) -> a -> b
$ do
MutableByteArray s
dst <- Int -> ST s (MutableByteArray (PrimState (ST s)))
forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
nScaled
MutableByteArray (PrimState (ST s))
-> Int -> ByteArray -> Int -> Int -> ST s ()
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> ByteArray -> Int -> Int -> m ()
PM.copyByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst Int
0 ByteArray
b Int
ixScaled Int
nScaled
MutableByteArray (PrimState (ST s)) -> ST s ByteArray
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
PM.unsafeFreezeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst
in Vector# n a -> Vector n a
forall (a :: Nat) (b :: TYPE R). Vector# a b -> Vector a b
V.Vector (A# a -> Vector# n a
forall (a :: TYPE R) (n :: Nat). A# a -> Vector# n a
V.unsafeConstruct# (ByteArray# -> A# a
forall a. ByteArray# -> PrimArray# a
PrimArray# ByteArray#
result))
where
sz :: Int
sz = ByteArray -> Int
PM.sizeofByteArray ByteArray
b
ixScaled :: Int
ixScaled = Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
E.size
nScaled :: Int
nScaled = Int# -> Int
I# (Nat# n -> Int#
forall (n :: Nat). Nat# n -> Int#
Nat.demote# Nat# n
n) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
E.size