{-# LANGUAGE TypeFamilies #-} module Data.Mat3x3 where import Control.Monad.ST import Data.Function import Data.Primitive import qualified Data.Vector.Generic as G import qualified Data.Vector.Generic.Mutable as GM import qualified Data.Vector.Unboxed as U import qualified Data.Vector.Unboxed.Mutable as UM import GHC.Exts data Mat3x3 a = Mat3x3 !Int !ByteArray instance (Prim a, Eq a) => Eq (Mat3x3 a) where == :: Mat3x3 a -> Mat3x3 a -> Bool (==) = [a] -> [a] -> Bool forall a. Eq a => a -> a -> Bool (==) ([a] -> [a] -> Bool) -> (Mat3x3 a -> [a]) -> Mat3x3 a -> Mat3x3 a -> Bool forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c `on` Mat3x3 a -> [a] Mat3x3 a -> [Item (Mat3x3 a)] forall l. IsList l => l -> [Item l] toList instance (Prim a, Show a) => Show (Mat3x3 a) where show :: Mat3x3 a -> String show = [a] -> String forall a. Show a => a -> String show ([a] -> String) -> (Mat3x3 a -> [a]) -> Mat3x3 a -> String forall b c a. (b -> c) -> (a -> b) -> a -> c . Mat3x3 a -> [a] Mat3x3 a -> [Item (Mat3x3 a)] forall l. IsList l => l -> [Item l] toList instance (Prim a) => IsList (Mat3x3 a) where type Item (Mat3x3 a) = a fromList :: [Item (Mat3x3 a)] -> Mat3x3 a fromList = Int -> ByteArray -> Mat3x3 a forall {k} (a :: k). Int -> ByteArray -> Mat3x3 a Mat3x3 Int 0 (ByteArray -> Mat3x3 a) -> ([a] -> ByteArray) -> [a] -> Mat3x3 a forall b c a. (b -> c) -> (a -> b) -> a -> c . Int -> [a] -> ByteArray forall a. Prim a => Int -> [a] -> ByteArray byteArrayFromListN Int 9 toList :: Mat3x3 a -> [Item (Mat3x3 a)] toList (Mat3x3 Int o ByteArray ba) = (Int -> a) -> [Int] -> [a] forall a b. (a -> b) -> [a] -> [b] map (ByteArray -> Int -> a forall a. Prim a => ByteArray -> Int -> a indexByteArray ByteArray ba) [Int o .. Int o Int -> Int -> Int forall a. Num a => a -> a -> a + Int 8] appMat3x3 :: (Prim a, Num a) => Mat3x3 a -> a -> a -> a -> (a, a, a) appMat3x3 :: forall a. (Prim a, Num a) => Mat3x3 a -> a -> a -> a -> (a, a, a) appMat3x3 (Mat3x3 Int o ByteArray ba) a x a y a z = (a x', a y', a z') where !x' :: a x' = a x a -> a -> a forall a. Num a => a -> a -> a * ByteArray -> Int -> a forall a. Prim a => ByteArray -> Int -> a indexByteArray ByteArray ba (Int o Int -> Int -> Int forall a. Num a => a -> a -> a + Int 0) a -> a -> a forall a. Num a => a -> a -> a + a y a -> a -> a forall a. Num a => a -> a -> a * ByteArray -> Int -> a forall a. Prim a => ByteArray -> Int -> a indexByteArray ByteArray ba (Int o Int -> Int -> Int forall a. Num a => a -> a -> a + Int 1) a -> a -> a forall a. Num a => a -> a -> a + a z a -> a -> a forall a. Num a => a -> a -> a * ByteArray -> Int -> a forall a. Prim a => ByteArray -> Int -> a indexByteArray ByteArray ba (Int o Int -> Int -> Int forall a. Num a => a -> a -> a + Int 2) !y' :: a y' = a x a -> a -> a forall a. Num a => a -> a -> a * ByteArray -> Int -> a forall a. Prim a => ByteArray -> Int -> a indexByteArray ByteArray ba (Int o Int -> Int -> Int forall a. Num a => a -> a -> a + Int 3) a -> a -> a forall a. Num a => a -> a -> a + a y a -> a -> a forall a. Num a => a -> a -> a * ByteArray -> Int -> a forall a. Prim a => ByteArray -> Int -> a indexByteArray ByteArray ba (Int o Int -> Int -> Int forall a. Num a => a -> a -> a + Int 4) a -> a -> a forall a. Num a => a -> a -> a + a z a -> a -> a forall a. Num a => a -> a -> a * ByteArray -> Int -> a forall a. Prim a => ByteArray -> Int -> a indexByteArray ByteArray ba (Int o Int -> Int -> Int forall a. Num a => a -> a -> a + Int 5) !z' :: a z' = a x a -> a -> a forall a. Num a => a -> a -> a * ByteArray -> Int -> a forall a. Prim a => ByteArray -> Int -> a indexByteArray ByteArray ba (Int o Int -> Int -> Int forall a. Num a => a -> a -> a + Int 6) a -> a -> a forall a. Num a => a -> a -> a + a y a -> a -> a forall a. Num a => a -> a -> a * ByteArray -> Int -> a forall a. Prim a => ByteArray -> Int -> a indexByteArray ByteArray ba (Int o Int -> Int -> Int forall a. Num a => a -> a -> a + Int 7) a -> a -> a forall a. Num a => a -> a -> a + a z a -> a -> a forall a. Num a => a -> a -> a * ByteArray -> Int -> a forall a. Prim a => ByteArray -> Int -> a indexByteArray ByteArray ba (Int o Int -> Int -> Int forall a. Num a => a -> a -> a + Int 8) rep3 :: (Int -> ST s ()) -> ST s () rep3 :: forall s. (Int -> ST s ()) -> ST s () rep3 Int -> ST s () f = Int -> ST s () f Int 0 ST s () -> ST s () -> ST s () forall a b. ST s a -> ST s b -> ST s b forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b *> Int -> ST s () f Int 1 ST s () -> ST s () -> ST s () forall a b. ST s a -> ST s b -> ST s b forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b *> Int -> ST s () f Int 2 {-# INLINE rep3 #-} rep9 :: (Int -> ST s ()) -> ST s () rep9 :: forall s. (Int -> ST s ()) -> ST s () rep9 Int -> ST s () f = Int -> ST s () f Int 0 ST s () -> ST s () -> ST s () forall a b. ST s a -> ST s b -> ST s b forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b *> Int -> ST s () f Int 1 ST s () -> ST s () -> ST s () forall a b. ST s a -> ST s b -> ST s b forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b *> Int -> ST s () f Int 2 ST s () -> ST s () -> ST s () forall a b. ST s a -> ST s b -> ST s b forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b *> Int -> ST s () f Int 3 ST s () -> ST s () -> ST s () forall a b. ST s a -> ST s b -> ST s b forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b *> Int -> ST s () f Int 4 ST s () -> ST s () -> ST s () forall a b. ST s a -> ST s b -> ST s b forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b *> Int -> ST s () f Int 5 ST s () -> ST s () -> ST s () forall a b. ST s a -> ST s b -> ST s b forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b *> Int -> ST s () f Int 6 ST s () -> ST s () -> ST s () forall a b. ST s a -> ST s b -> ST s b forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b *> Int -> ST s () f Int 7 ST s () -> ST s () -> ST s () forall a b. ST s a -> ST s b -> ST s b forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b *> Int -> ST s () f Int 8 {-# INLINE rep9 #-} createMat3x3 :: forall a. (Prim a) => (forall s. MutableByteArray s -> ST s ()) -> Mat3x3 a createMat3x3 :: forall a. Prim a => (forall s. MutableByteArray s -> ST s ()) -> Mat3x3 a createMat3x3 forall s. MutableByteArray s -> ST s () run = (forall s. ST s (Mat3x3 a)) -> Mat3x3 a forall a. (forall s. ST s a) -> a runST ((forall s. ST s (Mat3x3 a)) -> Mat3x3 a) -> (forall s. ST s (Mat3x3 a)) -> Mat3x3 a forall a b. (a -> b) -> a -> b $ do mba <- Int -> ST s (MutableByteArray (PrimState (ST s))) forall (m :: * -> *). PrimMonad m => Int -> m (MutableByteArray (PrimState m)) newByteArray (forall a. Prim a => a -> Int sizeOf @a a forall a. HasCallStack => a undefined Int -> Int -> Int forall a. Num a => a -> a -> a * Int 9) run mba Mat3x3 0 <$> unsafeFreezeByteArray mba genMat3x3 :: (Prim a) => (Int -> Int -> a) -> Mat3x3 a genMat3x3 :: forall a. Prim a => (Int -> Int -> a) -> Mat3x3 a genMat3x3 Int -> Int -> a f = (forall s. MutableByteArray s -> ST s ()) -> Mat3x3 a forall a. Prim a => (forall s. MutableByteArray s -> ST s ()) -> Mat3x3 a createMat3x3 ((forall s. MutableByteArray s -> ST s ()) -> Mat3x3 a) -> (forall s. MutableByteArray s -> ST s ()) -> Mat3x3 a forall a b. (a -> b) -> a -> b $ \MutableByteArray s mba -> do (Int -> ST s ()) -> ST s () forall s. (Int -> ST s ()) -> ST s () rep3 ((Int -> ST s ()) -> ST s ()) -> (Int -> ST s ()) -> ST s () forall a b. (a -> b) -> a -> b $ \Int i -> do (Int -> ST s ()) -> ST s () forall s. (Int -> ST s ()) -> ST s () rep3 ((Int -> ST s ()) -> ST s ()) -> (Int -> ST s ()) -> ST s () forall a b. (a -> b) -> a -> b $ \Int j -> do MutableByteArray (PrimState (ST s)) -> Int -> a -> ST s () forall a (m :: * -> *). (Prim a, PrimMonad m) => MutableByteArray (PrimState m) -> Int -> a -> m () writeByteArray MutableByteArray s MutableByteArray (PrimState (ST s)) mba (Int 3 Int -> Int -> Int forall a. Num a => a -> a -> a * Int i Int -> Int -> Int forall a. Num a => a -> a -> a + Int j) (Int -> Int -> a f Int i Int j) instance (Prim a, Num a) => Num (Mat3x3 a) where (Mat3x3 Int ox ByteArray xs) + :: Mat3x3 a -> Mat3x3 a -> Mat3x3 a + (Mat3x3 Int oy ByteArray ys) = (forall s. MutableByteArray s -> ST s ()) -> Mat3x3 a forall a. Prim a => (forall s. MutableByteArray s -> ST s ()) -> Mat3x3 a createMat3x3 ((forall s. MutableByteArray s -> ST s ()) -> Mat3x3 a) -> (forall s. MutableByteArray s -> ST s ()) -> Mat3x3 a forall a b. (a -> b) -> a -> b $ \MutableByteArray s mba -> (Int -> ST s ()) -> ST s () forall s. (Int -> ST s ()) -> ST s () rep9 ((Int -> ST s ()) -> ST s ()) -> (Int -> ST s ()) -> ST s () forall a b. (a -> b) -> a -> b $ \Int i -> do forall a (m :: * -> *). (Prim a, PrimMonad m) => MutableByteArray (PrimState m) -> Int -> a -> m () writeByteArray @a MutableByteArray s MutableByteArray (PrimState (ST s)) mba Int i (a -> ST s ()) -> a -> ST s () forall a b. (a -> b) -> a -> b $ ByteArray -> Int -> a forall a. Prim a => ByteArray -> Int -> a indexByteArray ByteArray xs (Int ox Int -> Int -> Int forall a. Num a => a -> a -> a + Int i) a -> a -> a forall a. Num a => a -> a -> a + ByteArray -> Int -> a forall a. Prim a => ByteArray -> Int -> a indexByteArray ByteArray ys (Int oy Int -> Int -> Int forall a. Num a => a -> a -> a + Int i) (Mat3x3 Int ox ByteArray xs) - :: Mat3x3 a -> Mat3x3 a -> Mat3x3 a - (Mat3x3 Int oy ByteArray ys) = (forall s. MutableByteArray s -> ST s ()) -> Mat3x3 a forall a. Prim a => (forall s. MutableByteArray s -> ST s ()) -> Mat3x3 a createMat3x3 ((forall s. MutableByteArray s -> ST s ()) -> Mat3x3 a) -> (forall s. MutableByteArray s -> ST s ()) -> Mat3x3 a forall a b. (a -> b) -> a -> b $ \MutableByteArray s mba -> (Int -> ST s ()) -> ST s () forall s. (Int -> ST s ()) -> ST s () rep9 ((Int -> ST s ()) -> ST s ()) -> (Int -> ST s ()) -> ST s () forall a b. (a -> b) -> a -> b $ \Int i -> do forall a (m :: * -> *). (Prim a, PrimMonad m) => MutableByteArray (PrimState m) -> Int -> a -> m () writeByteArray @a MutableByteArray s MutableByteArray (PrimState (ST s)) mba Int i (a -> ST s ()) -> a -> ST s () forall a b. (a -> b) -> a -> b $ ByteArray -> Int -> a forall a. Prim a => ByteArray -> Int -> a indexByteArray ByteArray xs (Int ox Int -> Int -> Int forall a. Num a => a -> a -> a + Int i) a -> a -> a forall a. Num a => a -> a -> a - ByteArray -> Int -> a forall a. Prim a => ByteArray -> Int -> a indexByteArray ByteArray ys (Int oy Int -> Int -> Int forall a. Num a => a -> a -> a + Int i) (Mat3x3 Int ox ByteArray xs) * :: Mat3x3 a -> Mat3x3 a -> Mat3x3 a * (Mat3x3 Int oy ByteArray ys) = (forall s. MutableByteArray s -> ST s ()) -> Mat3x3 a forall a. Prim a => (forall s. MutableByteArray s -> ST s ()) -> Mat3x3 a createMat3x3 ((forall s. MutableByteArray s -> ST s ()) -> Mat3x3 a) -> (forall s. MutableByteArray s -> ST s ()) -> Mat3x3 a forall a b. (a -> b) -> a -> b $ \MutableByteArray s mba -> do (Int -> ST s ()) -> ST s () forall s. (Int -> ST s ()) -> ST s () rep3 ((Int -> ST s ()) -> ST s ()) -> (Int -> ST s ()) -> ST s () forall a b. (a -> b) -> a -> b $ \Int i -> do let !ox' :: Int ox' = Int ox Int -> Int -> Int forall a. Num a => a -> a -> a + Int 3 Int -> Int -> Int forall a. Num a => a -> a -> a * Int i (Int -> ST s ()) -> ST s () forall s. (Int -> ST s ()) -> ST s () rep3 ((Int -> ST s ()) -> ST s ()) -> (Int -> ST s ()) -> ST s () forall a b. (a -> b) -> a -> b $ \Int j -> do let !oy' :: Int oy' = Int oy Int -> Int -> Int forall a. Num a => a -> a -> a + Int j forall a (m :: * -> *). (Prim a, PrimMonad m) => MutableByteArray (PrimState m) -> Int -> a -> m () writeByteArray @a MutableByteArray s MutableByteArray (PrimState (ST s)) mba (Int 3 Int -> Int -> Int forall a. Num a => a -> a -> a * Int i Int -> Int -> Int forall a. Num a => a -> a -> a + Int j) (a -> ST s ()) -> a -> ST s () forall a b. (a -> b) -> a -> b $ ByteArray -> Int -> a forall a. Prim a => ByteArray -> Int -> a indexByteArray ByteArray xs Int ox' a -> a -> a forall a. Num a => a -> a -> a * ByteArray -> Int -> a forall a. Prim a => ByteArray -> Int -> a indexByteArray ByteArray ys Int oy' a -> a -> a forall a. Num a => a -> a -> a + ByteArray -> Int -> a forall a. Prim a => ByteArray -> Int -> a indexByteArray ByteArray xs (Int ox' Int -> Int -> Int forall a. Num a => a -> a -> a + Int 1) a -> a -> a forall a. Num a => a -> a -> a * ByteArray -> Int -> a forall a. Prim a => ByteArray -> Int -> a indexByteArray ByteArray ys (Int oy' Int -> Int -> Int forall a. Num a => a -> a -> a + Int 3) a -> a -> a forall a. Num a => a -> a -> a + ByteArray -> Int -> a forall a. Prim a => ByteArray -> Int -> a indexByteArray ByteArray xs (Int ox' Int -> Int -> Int forall a. Num a => a -> a -> a + Int 2) a -> a -> a forall a. Num a => a -> a -> a * ByteArray -> Int -> a forall a. Prim a => ByteArray -> Int -> a indexByteArray ByteArray ys (Int oy' Int -> Int -> Int forall a. Num a => a -> a -> a + Int 6) negate :: Mat3x3 a -> Mat3x3 a negate (Mat3x3 Int ox ByteArray xs) = (forall s. MutableByteArray s -> ST s ()) -> Mat3x3 a forall a. Prim a => (forall s. MutableByteArray s -> ST s ()) -> Mat3x3 a createMat3x3 ((forall s. MutableByteArray s -> ST s ()) -> Mat3x3 a) -> (forall s. MutableByteArray s -> ST s ()) -> Mat3x3 a forall a b. (a -> b) -> a -> b $ \MutableByteArray s mba -> (Int -> ST s ()) -> ST s () forall s. (Int -> ST s ()) -> ST s () rep9 ((Int -> ST s ()) -> ST s ()) -> (Int -> ST s ()) -> ST s () forall a b. (a -> b) -> a -> b $ \Int i -> do forall a (m :: * -> *). (Prim a, PrimMonad m) => MutableByteArray (PrimState m) -> Int -> a -> m () writeByteArray @a MutableByteArray s MutableByteArray (PrimState (ST s)) mba Int i (a -> ST s ()) -> (a -> a) -> a -> ST s () forall b c a. (b -> c) -> (a -> b) -> a -> c . a -> a forall a. Num a => a -> a negate (a -> ST s ()) -> a -> ST s () forall a b. (a -> b) -> a -> b $ ByteArray -> Int -> a forall a. Prim a => ByteArray -> Int -> a indexByteArray ByteArray xs (Int ox Int -> Int -> Int forall a. Num a => a -> a -> a + Int i) abs :: Mat3x3 a -> Mat3x3 a abs = Mat3x3 a -> Mat3x3 a forall a. a -> a id signum :: Mat3x3 a -> Mat3x3 a signum = Mat3x3 a -> Mat3x3 a -> Mat3x3 a forall a b. a -> b -> a const Mat3x3 a 1 fromInteger :: Integer -> Mat3x3 a fromInteger Integer x = (forall s. MutableByteArray s -> ST s ()) -> Mat3x3 a forall a. Prim a => (forall s. MutableByteArray s -> ST s ()) -> Mat3x3 a createMat3x3 ((forall s. MutableByteArray s -> ST s ()) -> Mat3x3 a) -> (forall s. MutableByteArray s -> ST s ()) -> Mat3x3 a forall a b. (a -> b) -> a -> b $ \MutableByteArray s mba -> do forall a (m :: * -> *). (Prim a, PrimMonad m) => MutableByteArray (PrimState m) -> Int -> Int -> a -> m () setByteArray @a MutableByteArray s MutableByteArray (PrimState (ST s)) mba Int 0 Int 9 a 0 forall a (m :: * -> *). (Prim a, PrimMonad m) => MutableByteArray (PrimState m) -> Int -> a -> m () writeByteArray @a MutableByteArray s MutableByteArray (PrimState (ST s)) mba Int 0 (Integer -> a forall a b. (Integral a, Num b) => a -> b fromIntegral Integer x) forall a (m :: * -> *). (Prim a, PrimMonad m) => MutableByteArray (PrimState m) -> Int -> a -> m () writeByteArray @a MutableByteArray s MutableByteArray (PrimState (ST s)) mba Int 4 (Integer -> a forall a b. (Integral a, Num b) => a -> b fromIntegral Integer x) forall a (m :: * -> *). (Prim a, PrimMonad m) => MutableByteArray (PrimState m) -> Int -> a -> m () writeByteArray @a MutableByteArray s MutableByteArray (PrimState (ST s)) mba Int 8 (Integer -> a forall a b. (Integral a, Num b) => a -> b fromIntegral Integer x) data instance UM.MVector s (Mat3x3 a) = MV_Mat3x3 !Int !Int !(MutableByteArray s) data instance U.Vector (Mat3x3 a) = V_Mat3x3 !Int !Int !ByteArray instance (Prim a) => U.Unbox (Mat3x3 a) instance (Prim a) => GM.MVector UM.MVector (Mat3x3 a) where basicLength :: forall s. MVector s (Mat3x3 a) -> Int basicLength (MV_Mat3x3 Int _ Int n MutableByteArray s _) = Int -> Int -> Int forall a. Integral a => a -> a -> a quot Int n Int 9 {-# INLINE basicLength #-} basicUnsafeSlice :: forall s. Int -> Int -> MVector s (Mat3x3 a) -> MVector s (Mat3x3 a) basicUnsafeSlice Int i Int n (MV_Mat3x3 Int o Int _ MutableByteArray s mba) = Int -> Int -> MutableByteArray s -> MVector s (Mat3x3 a) forall k s (a :: k). Int -> Int -> MutableByteArray s -> MVector s (Mat3x3 a) MV_Mat3x3 (Int o Int -> Int -> Int forall a. Num a => a -> a -> a + Int 9 Int -> Int -> Int forall a. Num a => a -> a -> a * Int i) (Int 9 Int -> Int -> Int forall a. Num a => a -> a -> a * Int n) MutableByteArray s mba {-# INLINE basicUnsafeSlice #-} basicOverlaps :: forall s. MVector s (Mat3x3 a) -> MVector s (Mat3x3 a) -> Bool basicOverlaps (MV_Mat3x3 Int ox Int nx MutableByteArray s xs) (MV_Mat3x3 Int oy Int ny MutableByteArray s ys) = MutableByteArray s -> MutableByteArray s -> Bool forall s. MutableByteArray s -> MutableByteArray s -> Bool sameMutableByteArray MutableByteArray s xs MutableByteArray s ys Bool -> Bool -> Bool && Int ox Int -> Int -> Bool forall a. Ord a => a -> a -> Bool < Int oy Int -> Int -> Int forall a. Num a => a -> a -> a + Int ny Bool -> Bool -> Bool && Int oy Int -> Int -> Bool forall a. Ord a => a -> a -> Bool < Int ox Int -> Int -> Int forall a. Num a => a -> a -> a + Int nx {-# INLINE basicOverlaps #-} basicUnsafeNew :: forall s. Int -> ST s (MVector s (Mat3x3 a)) basicUnsafeNew Int n = Int -> Int -> MutableByteArray s -> MVector s (Mat3x3 a) forall k s (a :: k). Int -> Int -> MutableByteArray s -> MVector s (Mat3x3 a) MV_Mat3x3 Int 0 (Int 9 Int -> Int -> Int forall a. Num a => a -> a -> a * Int n) (MutableByteArray s -> MVector s (Mat3x3 a)) -> ST s (MutableByteArray s) -> ST s (MVector s (Mat3x3 a)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Int -> ST s (MutableByteArray (PrimState (ST s))) forall (m :: * -> *). PrimMonad m => Int -> m (MutableByteArray (PrimState m)) newByteArray (forall a. Prim a => a -> Int sizeOf @a a forall a. HasCallStack => a undefined Int -> Int -> Int forall a. Num a => a -> a -> a * Int 9 Int -> Int -> Int forall a. Num a => a -> a -> a * Int n) {-# INLINE basicUnsafeNew #-} basicInitialize :: forall s. MVector s (Mat3x3 a) -> ST s () basicInitialize (MV_Mat3x3 Int o Int n MutableByteArray s mba) = MutableByteArray (PrimState (ST s)) -> Int -> Int -> Word8 -> ST s () forall (m :: * -> *). PrimMonad m => MutableByteArray (PrimState m) -> Int -> Int -> Word8 -> m () fillByteArray MutableByteArray s MutableByteArray (PrimState (ST s)) mba (Int sz Int -> Int -> Int forall a. Num a => a -> a -> a * Int o) (Int sz Int -> Int -> Int forall a. Num a => a -> a -> a * Int n) Word8 0 where sz :: Int sz = forall a. Prim a => a -> Int sizeOf @a a forall a. HasCallStack => a undefined {-# INLINE basicInitialize #-} basicUnsafeRead :: forall s. MVector s (Mat3x3 a) -> Int -> ST s (Mat3x3 a) basicUnsafeRead (MV_Mat3x3 Int o Int _ MutableByteArray s mba) Int i = do dst <- Int -> ST s (MutableByteArray (PrimState (ST s))) forall (m :: * -> *). PrimMonad m => Int -> m (MutableByteArray (PrimState m)) newByteArray (Int sz Int -> Int -> Int forall a. Num a => a -> a -> a * Int 9) copyMutableByteArray dst 0 mba (sz * (o + 9 * i)) (sz * 9) Mat3x3 0 <$> unsafeFreezeByteArray dst where sz :: Int sz = forall a. Prim a => a -> Int sizeOf @a a forall a. HasCallStack => a undefined {-# INLINE basicUnsafeRead #-} basicUnsafeWrite :: forall s. MVector s (Mat3x3 a) -> Int -> Mat3x3 a -> ST s () basicUnsafeWrite (MV_Mat3x3 Int o Int _ MutableByteArray s mba) Int i (Mat3x3 Int o' ByteArray ba) = MutableByteArray (PrimState (ST s)) -> Int -> ByteArray -> Int -> Int -> ST s () forall (m :: * -> *). PrimMonad m => MutableByteArray (PrimState m) -> Int -> ByteArray -> Int -> Int -> m () copyByteArray MutableByteArray s MutableByteArray (PrimState (ST s)) mba (Int sz Int -> Int -> Int forall a. Num a => a -> a -> a * (Int o Int -> Int -> Int forall a. Num a => a -> a -> a + Int 9 Int -> Int -> Int forall a. Num a => a -> a -> a * Int i)) ByteArray ba (Int sz Int -> Int -> Int forall a. Num a => a -> a -> a * Int o') (Int sz Int -> Int -> Int forall a. Num a => a -> a -> a * Int 9) where sz :: Int sz = forall a. Prim a => a -> Int sizeOf @a a forall a. HasCallStack => a undefined {-# INLINE basicUnsafeWrite #-} basicUnsafeCopy :: forall s. MVector s (Mat3x3 a) -> MVector s (Mat3x3 a) -> ST s () basicUnsafeCopy (MV_Mat3x3 Int o Int n MutableByteArray s dst) (MV_Mat3x3 Int o' Int _ MutableByteArray s src) = MutableByteArray (PrimState (ST s)) -> Int -> MutableByteArray (PrimState (ST s)) -> Int -> Int -> ST s () forall (m :: * -> *). PrimMonad m => MutableByteArray (PrimState m) -> Int -> MutableByteArray (PrimState m) -> Int -> Int -> m () copyMutableByteArray MutableByteArray s MutableByteArray (PrimState (ST s)) dst (Int sz Int -> Int -> Int forall a. Num a => a -> a -> a * Int o) MutableByteArray s MutableByteArray (PrimState (ST s)) src (Int sz Int -> Int -> Int forall a. Num a => a -> a -> a * Int o') (Int sz Int -> Int -> Int forall a. Num a => a -> a -> a * Int n) where sz :: Int sz = forall a. Prim a => a -> Int sizeOf @a a forall a. HasCallStack => a undefined {-# INLINE basicUnsafeCopy #-} instance (Prim a) => G.Vector U.Vector (Mat3x3 a) where basicUnsafeFreeze :: forall s. Mutable Vector s (Mat3x3 a) -> ST s (Vector (Mat3x3 a)) basicUnsafeFreeze (MV_Mat3x3 Int o Int n MutableByteArray s mba) = Int -> Int -> ByteArray -> Vector (Mat3x3 a) forall k (a :: k). Int -> Int -> ByteArray -> Vector (Mat3x3 a) V_Mat3x3 Int o Int n (ByteArray -> Vector (Mat3x3 a)) -> ST s ByteArray -> ST s (Vector (Mat3x3 a)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> MutableByteArray (PrimState (ST s)) -> ST s ByteArray forall (m :: * -> *). PrimMonad m => MutableByteArray (PrimState m) -> m ByteArray unsafeFreezeByteArray MutableByteArray s MutableByteArray (PrimState (ST s)) mba {-# INLINE basicUnsafeFreeze #-} basicUnsafeThaw :: forall s. Vector (Mat3x3 a) -> ST s (Mutable Vector s (Mat3x3 a)) basicUnsafeThaw (V_Mat3x3 Int o Int n ByteArray ba) = Int -> Int -> MutableByteArray s -> MVector s (Mat3x3 a) forall k s (a :: k). Int -> Int -> MutableByteArray s -> MVector s (Mat3x3 a) MV_Mat3x3 Int o Int n (MutableByteArray s -> MVector s (Mat3x3 a)) -> ST s (MutableByteArray s) -> ST s (MVector s (Mat3x3 a)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> ByteArray -> ST s (MutableByteArray (PrimState (ST s))) forall (m :: * -> *). PrimMonad m => ByteArray -> m (MutableByteArray (PrimState m)) unsafeThawByteArray ByteArray ba {-# INLINE basicUnsafeThaw #-} basicLength :: Vector (Mat3x3 a) -> Int basicLength (V_Mat3x3 Int _ Int n ByteArray _) = Int -> Int -> Int forall a. Integral a => a -> a -> a quot Int n Int 9 {-# INLINE basicLength #-} basicUnsafeSlice :: Int -> Int -> Vector (Mat3x3 a) -> Vector (Mat3x3 a) basicUnsafeSlice Int i Int n (V_Mat3x3 Int o Int _ ByteArray ba) = Int -> Int -> ByteArray -> Vector (Mat3x3 a) forall k (a :: k). Int -> Int -> ByteArray -> Vector (Mat3x3 a) V_Mat3x3 (Int o Int -> Int -> Int forall a. Num a => a -> a -> a + Int 9 Int -> Int -> Int forall a. Num a => a -> a -> a * Int i) (Int 9 Int -> Int -> Int forall a. Num a => a -> a -> a * Int n) ByteArray ba {-# INLINE basicUnsafeSlice #-} basicUnsafeIndexM :: Vector (Mat3x3 a) -> Int -> Box (Mat3x3 a) basicUnsafeIndexM (V_Mat3x3 Int o Int _ ByteArray ba) Int i = Mat3x3 a -> Box (Mat3x3 a) forall a. a -> Box a forall (m :: * -> *) a. Monad m => a -> m a return (Mat3x3 a -> Box (Mat3x3 a)) -> Mat3x3 a -> Box (Mat3x3 a) forall a b. (a -> b) -> a -> b $! Int -> ByteArray -> Mat3x3 a forall {k} (a :: k). Int -> ByteArray -> Mat3x3 a Mat3x3 (Int o Int -> Int -> Int forall a. Num a => a -> a -> a + Int 9 Int -> Int -> Int forall a. Num a => a -> a -> a * Int i) ByteArray ba {-# INLINE basicUnsafeIndexM #-} basicUnsafeCopy :: forall s. Mutable Vector s (Mat3x3 a) -> Vector (Mat3x3 a) -> ST s () basicUnsafeCopy (MV_Mat3x3 Int o Int n MutableByteArray s dst) (V_Mat3x3 Int o' Int _ ByteArray src) = MutableByteArray (PrimState (ST s)) -> Int -> ByteArray -> Int -> Int -> ST s () forall (m :: * -> *). PrimMonad m => MutableByteArray (PrimState m) -> Int -> ByteArray -> Int -> Int -> m () copyByteArray MutableByteArray s MutableByteArray (PrimState (ST s)) dst (Int sz Int -> Int -> Int forall a. Num a => a -> a -> a * Int o) ByteArray src (Int sz Int -> Int -> Int forall a. Num a => a -> a -> a * Int o') (Int sz Int -> Int -> Int forall a. Num a => a -> a -> a * Int n) where sz :: Int sz = forall a. Prim a => a -> Int sizeOf @a a forall a. HasCallStack => a undefined elemseq :: forall b. Vector (Mat3x3 a) -> Mat3x3 a -> b -> b elemseq Vector (Mat3x3 a) _ = Mat3x3 a -> b -> b forall a b. a -> b -> b seq {-# INLINE elemseq #-}