{-# LANGUAGE ForeignFunctionInterface #-}
module AronFFI where
import Foreign
import Foreign.Storable
import Foreign.Ptr
import Foreign.C.Types
import Foreign.C.String
import System.IO.Unsafe
import Control.Monad
import Control.Lens
import AronModule
import qualified Data.Vector.Storable as V
import qualified Data.Vector.Storable.Mutable as VM
foreign import ccall "increment"
c_increment :: CInt -> IO CInt
f_increment :: Int -> IO Int
f_increment :: Int -> IO Int
f_increment Int
n = do
CInt
x <- CInt -> IO CInt
c_increment (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n)
Int -> IO Int
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> IO Int) -> Int -> IO Int
forall a b. (a -> b) -> a -> b
$ CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
x
foreign import ccall "print_ascii"
c_print_ascii :: IO()
f_print_ascii::IO()
f_print_ascii :: IO ()
f_print_ascii = IO ()
c_print_ascii
foreign import ccall "alloca_memory"
c_alloca_memory::Ptr CInt -> CInt -> IO()
foreign import ccall "dotn"
c_dotn:: CInt -> Ptr CDouble -> Ptr CDouble -> IO CDouble
f_dot :: [CDouble] -> [CDouble] -> IO CDouble
f_dot :: [CDouble] -> [CDouble] -> IO CDouble
f_dot [CDouble]
s1 [CDouble]
s2 = do
if [CDouble] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [CDouble]
s1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= [CDouble] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [CDouble]
s2 then [Char] -> IO CDouble
forall a. HasCallStack => [Char] -> a
error [Char]
"ERROR441: the length of two lists must be the same." else do
let n :: CInt
n = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> ([CDouble] -> Int) -> [CDouble] -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [CDouble] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length) [CDouble]
s1
[CDouble] -> (Int -> Ptr CDouble -> IO CDouble) -> IO CDouble
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [CDouble]
s1 ((Int -> Ptr CDouble -> IO CDouble) -> IO CDouble)
-> (Int -> Ptr CDouble -> IO CDouble) -> IO CDouble
forall a b. (a -> b) -> a -> b
$ \Int
l1 Ptr CDouble
pt1 ->
[CDouble] -> (Int -> Ptr CDouble -> IO CDouble) -> IO CDouble
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [CDouble]
s2 ((Int -> Ptr CDouble -> IO CDouble) -> IO CDouble)
-> (Int -> Ptr CDouble -> IO CDouble) -> IO CDouble
forall a b. (a -> b) -> a -> b
$ \Int
l2 Ptr CDouble
pt2 ->
CInt -> Ptr CDouble -> Ptr CDouble -> IO CDouble
c_dotn CInt
n Ptr CDouble
pt1 Ptr CDouble
pt2
foreign import ccall "addVec"
c_addVec:: CInt -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO()
foreign import ccall "subVec3"
c_subVec3:: Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO()
foreign import ccall "mulScaleVec3"
c_mulScaleVec3:: CDouble -> Ptr CDouble -> Ptr CDouble -> IO()
foreign import ccall "mulVec3Scale"
c_mulVec3Scale:: Ptr CDouble -> CDouble -> Ptr CDouble -> IO()
foreign import ccall "multiVec"
c_multiVec:: CInt -> CInt -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO()
foreign import ccall "multiMat"
c_multiMat:: CInt -> CInt -> Ptr CDouble -> CInt -> CInt -> Ptr CDouble -> Ptr CDouble -> IO()
foreign import ccall "quickSortInt"
c_quickSortInt:: CInt -> CInt -> Ptr CInt -> IO()
f_quickSortInt :: [Int] -> IO [Int]
f_quickSortInt :: [Int] -> IO [Int]
f_quickSortInt [Int]
cx = do
let cx' :: [CInt]
cx' = (Int -> CInt) -> [Int] -> [CInt]
forall a b. (a -> b) -> [a] -> [b]
map Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral [Int]
cx
let vs :: Vector CInt
vs = [CInt] -> Vector CInt
forall a. Storable a => [a] -> Vector a
V.fromList ([CInt]
cx')
IOVector CInt
v <- Vector CInt -> IO (MVector (PrimState IO) CInt)
forall a (m :: * -> *).
(Storable a, PrimMonad m) =>
Vector a -> m (MVector (PrimState m) a)
V.thaw Vector CInt
vs
IOVector CInt -> (Ptr CInt -> IO ()) -> IO ()
forall a b. Storable a => IOVector a -> (Ptr a -> IO b) -> IO b
VM.unsafeWith IOVector CInt
v ((Ptr CInt -> IO ()) -> IO ()) -> (Ptr CInt -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
pt ->
CInt -> CInt -> Ptr CInt -> IO ()
c_quickSortInt CInt
0 ([CInt] -> CInt
forall (t :: * -> *) b a. (Foldable t, Num b) => t a -> b
len [CInt]
cx' CInt -> CInt -> CInt
forall a. Num a => a -> a -> a
- CInt
1) Ptr CInt
pt
[Int]
out <- MVector (PrimState IO) CInt -> IO (Vector CInt)
forall a (m :: * -> *).
(Storable a, PrimMonad m) =>
MVector (PrimState m) a -> m (Vector a)
V.freeze IOVector CInt
MVector (PrimState IO) CInt
v IO (Vector CInt) -> (Vector CInt -> [CInt]) -> IO [CInt]
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> Vector CInt -> [CInt]
forall a. Storable a => Vector a -> [a]
V.toList IO [CInt] -> ([CInt] -> [Int]) -> IO [Int]
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (CInt -> Int) -> [CInt] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
[Int] -> IO [Int]
forall (m :: * -> *) a. Monad m => a -> m a
return [Int]
out
f_multiMat :: [[Double]] -> [[Double]] -> IO [[Double]]
f_multiMat :: [[Double]] -> [[Double]] -> IO [[Double]]
f_multiMat [[Double]]
cs [[Double]]
cx = do
let fx :: Int -> CInt
fx = Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral
let (Int
h, Int
w) = [[Double]] -> (Int, Int)
forall (t :: * -> *) a. Foldable t => [t a] -> (Int, Int)
dim [[Double]]
cs
let (Int
h', Int
w') = [[Double]] -> (Int, Int)
forall (t :: * -> *) a. Foldable t => [t a] -> (Int, Int)
dim [[Double]]
cx
if Int
w Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
w' Bool -> Bool -> Bool
&& Int
h Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
h' then do
let cs' :: [CDouble]
cs' = (Double -> CDouble) -> [Double] -> [CDouble]
forall a b. (a -> b) -> [a] -> [b]
map Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac ([Double] -> [CDouble]) -> [Double] -> [CDouble]
forall a b. (a -> b) -> a -> b
$ [[Double]] -> [Double]
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join [[Double]]
cs
let cx' :: [CDouble]
cx' = (Double -> CDouble) -> [Double] -> [CDouble]
forall a b. (a -> b) -> [a] -> [b]
map Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac ([Double] -> [CDouble]) -> [Double] -> [CDouble]
forall a b. (a -> b) -> a -> b
$ [[Double]] -> [Double]
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join [[Double]]
cx
let nBytes :: Int
nBytes = let n :: CDouble
n = CDouble
0 :: CDouble in Int
w Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
h Int -> Int -> Int
forall a. Num a => a -> a -> a
* CDouble -> Int
forall a. Storable a => a -> Int
sizeOf CDouble
n
Int -> (Ptr CDouble -> IO [[Double]]) -> IO [[Double]]
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
nBytes ((Ptr CDouble -> IO [[Double]]) -> IO [[Double]])
-> (Ptr CDouble -> IO [[Double]]) -> IO [[Double]]
forall a b. (a -> b) -> a -> b
$ \Ptr CDouble
pt -> do
[CDouble] -> (Int -> Ptr CDouble -> IO [[Double]]) -> IO [[Double]]
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [CDouble]
cs' ((Int -> Ptr CDouble -> IO [[Double]]) -> IO [[Double]])
-> (Int -> Ptr CDouble -> IO [[Double]]) -> IO [[Double]]
forall a b. (a -> b) -> a -> b
$ \Int
l1 Ptr CDouble
pt1 -> do
[CDouble] -> (Int -> Ptr CDouble -> IO [[Double]]) -> IO [[Double]]
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [CDouble]
cx' ((Int -> Ptr CDouble -> IO [[Double]]) -> IO [[Double]])
-> (Int -> Ptr CDouble -> IO [[Double]]) -> IO [[Double]]
forall a b. (a -> b) -> a -> b
$ \Int
l2 Ptr CDouble
pt2 -> do
CInt
-> CInt
-> Ptr CDouble
-> CInt
-> CInt
-> Ptr CDouble
-> Ptr CDouble
-> IO ()
c_multiMat (Int -> CInt
fx Int
h) (Int -> CInt
fx Int
w) Ptr CDouble
pt1 (Int -> CInt
fx Int
h') (Int -> CInt
fx Int
w') Ptr CDouble
pt2 Ptr CDouble
pt
[CDouble]
arr <- Int -> Ptr CDouble -> IO [CDouble]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray (Int
w Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
h) Ptr CDouble
pt
[[Double]] -> IO [[Double]]
forall (m :: * -> *) a. Monad m => a -> m a
return ([[Double]] -> IO [[Double]]) -> [[Double]] -> IO [[Double]]
forall a b. (a -> b) -> a -> b
$ Int -> [Double] -> [[Double]]
forall a. Int -> [a] -> [[a]]
fxx Int
w ([Double] -> [[Double]]) -> [Double] -> [[Double]]
forall a b. (a -> b) -> a -> b
$ (CDouble -> Double) -> [CDouble] -> [Double]
forall a b. (a -> b) -> [a] -> [b]
map CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac [CDouble]
arr
else do
[Char] -> IO [[Double]]
forall a. HasCallStack => [Char] -> a
error ([Char] -> IO [[Double]]) -> [Char] -> IO [[Double]]
forall a b. (a -> b) -> a -> b
$ [Char]
"ERROR114, Invalid dimension, w == w' && h == h'"
where
dim :: [t a] -> (Int, Int)
dim [t a]
x = (Int
h, Int
w)
where
w :: Int
w = case [t a]
x of
[] -> Int
0
vs:_ -> t a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length t a
vs
h :: Int
h = [t a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [t a]
x
fxx :: Int -> [a] -> [[a]]
fxx :: Int -> [a] -> [[a]]
fxx Int
_ [] = []
fxx Int
n [a]
cx = let ([a]
x, [a]
cx') = Int -> [a] -> ([a], [a])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
n [a]
cx in [a]
x [a] -> [[a]] -> [[a]]
forall a. a -> [a] -> [a]
: Int -> [a] -> [[a]]
forall a. Int -> [a] -> [[a]]
fxx Int
n [a]
cx'
f_multiVec :: [[Double]] -> [Double] -> IO [Double]
f_multiVec :: [[Double]] -> [Double] -> IO [Double]
f_multiVec [[Double]]
cx [Double]
v = do
if [[Double]] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[Double]]
cx Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 then do
let nRow :: Int
nRow = [[Double]] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[Double]]
cx
let nRow' :: CInt
nRow' = Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
nRow
let nCol :: Int
nCol = ([Double] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Double] -> Int) -> ([[Double]] -> [Double]) -> [[Double]] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Double]] -> [Double]
forall a. [a] -> a
head) [[Double]]
cx
let nCol' :: CInt
nCol' = Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
nCol
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
nCol Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= [Double] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Double]
v) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
[Char] -> IO ()
forall a. HasCallStack => [Char] -> a
error [Char]
"ERROR111: Invalid Input dimension, nCol /= length v"
let cx' :: [CDouble]
cx' = (Double -> CDouble) -> [Double] -> [CDouble]
forall a b. (a -> b) -> [a] -> [b]
map Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac ([Double] -> [CDouble]) -> [Double] -> [CDouble]
forall a b. (a -> b) -> a -> b
$ [[Double]] -> [Double]
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join [[Double]]
cx
let v' :: [CDouble]
v' = (Double -> CDouble) -> [Double] -> [CDouble]
forall a b. (a -> b) -> [a] -> [b]
map Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac [Double]
v
let nBytes :: Int
nBytes = Int
nCol Int -> Int -> Int
forall a. Num a => a -> a -> a
* CDouble -> Int
forall a. Storable a => a -> Int
sizeOf (CDouble
0::CDouble)
Int -> (Ptr CDouble -> IO [Double]) -> IO [Double]
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
nBytes ((Ptr CDouble -> IO [Double]) -> IO [Double])
-> (Ptr CDouble -> IO [Double]) -> IO [Double]
forall a b. (a -> b) -> a -> b
$ \Ptr CDouble
u -> do
[CDouble] -> (Int -> Ptr CDouble -> IO [Double]) -> IO [Double]
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [CDouble]
cx' ((Int -> Ptr CDouble -> IO [Double]) -> IO [Double])
-> (Int -> Ptr CDouble -> IO [Double]) -> IO [Double]
forall a b. (a -> b) -> a -> b
$ \Int
l1 Ptr CDouble
pt1 -> do
[CDouble] -> (Int -> Ptr CDouble -> IO [Double]) -> IO [Double]
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [CDouble]
v' ((Int -> Ptr CDouble -> IO [Double]) -> IO [Double])
-> (Int -> Ptr CDouble -> IO [Double]) -> IO [Double]
forall a b. (a -> b) -> a -> b
$ \Int
l2 Ptr CDouble
pt2 -> do
CInt -> CInt -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO ()
c_multiVec CInt
nRow' CInt
nCol' Ptr CDouble
pt1 Ptr CDouble
pt2 Ptr CDouble
u
[CDouble]
arr <- Int -> Ptr CDouble -> IO [CDouble]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
nCol Ptr CDouble
u
[Double] -> IO [Double]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Double] -> IO [Double]) -> [Double] -> IO [Double]
forall a b. (a -> b) -> a -> b
$ (CDouble -> Double) -> [CDouble] -> [Double]
forall a b. (a -> b) -> [a] -> [b]
map CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac [CDouble]
arr
else [Char] -> IO [Double]
forall a. HasCallStack => [Char] -> a
error [Char]
"ERROR112: Invalid Input, f_multiVec"
f_addVec :: [Double] -> [Double] -> IO [Double]
f_addVec :: [Double] -> [Double] -> IO [Double]
f_addVec [Double]
s1 [Double]
s2 = do
if [Double] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Double]
s1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= [Double] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Double]
s2 then [Char] -> IO [Double]
forall a. HasCallStack => [Char] -> a
error [Char]
"ERROR334: the length of two lists must be the same."
else do
let n :: Int
n = [Double] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Double]
s1
let s1' :: [CDouble]
s1' = (Double -> CDouble) -> [Double] -> [CDouble]
forall a b. (a -> b) -> [a] -> [b]
map Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac [Double]
s1
let s2' :: [CDouble]
s2' = (Double -> CDouble) -> [Double] -> [CDouble]
forall a b. (a -> b) -> [a] -> [b]
map Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac [Double]
s2
let nBytes :: Int
nBytes = let a :: CDouble
a = CDouble
0.0 :: CDouble in Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
* CDouble -> Int
forall a. Storable a => a -> Int
sizeOf CDouble
a
Int -> (Ptr CDouble -> IO [Double]) -> IO [Double]
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
nBytes ((Ptr CDouble -> IO [Double]) -> IO [Double])
-> (Ptr CDouble -> IO [Double]) -> IO [Double]
forall a b. (a -> b) -> a -> b
$ \Ptr CDouble
ptx -> do
[CDouble] -> (Int -> Ptr CDouble -> IO ()) -> IO ()
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [CDouble]
s1' (\Int
l1 Ptr CDouble
pt1 -> [CDouble] -> (Int -> Ptr CDouble -> IO ()) -> IO ()
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [CDouble]
s2' (\Int
l2 Ptr CDouble
pt2 -> CInt -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO ()
c_addVec (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l1) Ptr CDouble
pt1 Ptr CDouble
pt2 Ptr CDouble
ptx))
[CDouble]
arr <- Int -> Ptr CDouble -> IO [CDouble]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
n Ptr CDouble
ptx
[Double] -> IO [Double]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Double] -> IO [Double]) -> [Double] -> IO [Double]
forall a b. (a -> b) -> a -> b
$ (CDouble -> Double) -> [CDouble] -> [Double]
forall a b. (a -> b) -> [a] -> [b]
map CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac [CDouble]
arr
f_subVec3 :: [CDouble] -> [CDouble] -> IO [CDouble]
f_subVec3 :: [CDouble] -> [CDouble] -> IO [CDouble]
f_subVec3 [CDouble]
s1 [CDouble]
s2 = do
let n :: Int
n = Int
3
let nBytes :: Int
nBytes = let a :: CDouble
a = CDouble
1.0 :: CDouble in Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
* CDouble -> Int
forall a. Storable a => a -> Int
sizeOf CDouble
a
Int -> (Ptr CDouble -> IO [CDouble]) -> IO [CDouble]
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
nBytes ((Ptr CDouble -> IO [CDouble]) -> IO [CDouble])
-> (Ptr CDouble -> IO [CDouble]) -> IO [CDouble]
forall a b. (a -> b) -> a -> b
$ \Ptr CDouble
ptx -> do
[CDouble] -> (Int -> Ptr CDouble -> IO ()) -> IO ()
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [CDouble]
s1 ((Int -> Ptr CDouble -> IO ()) -> IO ())
-> (Int -> Ptr CDouble -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Int
l1 Ptr CDouble
pt1 ->
[CDouble] -> (Int -> Ptr CDouble -> IO ()) -> IO ()
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [CDouble]
s2 ((Int -> Ptr CDouble -> IO ()) -> IO ())
-> (Int -> Ptr CDouble -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Int
l2 Ptr CDouble
pt2 ->
Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO ()
c_subVec3 Ptr CDouble
pt1 Ptr CDouble
pt2 Ptr CDouble
ptx
[CDouble]
arr <- Int -> Ptr CDouble -> IO [CDouble]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
n Ptr CDouble
ptx
[CDouble] -> IO [CDouble]
forall (m :: * -> *) a. Monad m => a -> m a
return [CDouble]
arr
f_mulScaleVec3 :: CDouble -> [CDouble] -> IO [CDouble]
f_mulScaleVec3 :: CDouble -> [CDouble] -> IO [CDouble]
f_mulScaleVec3 CDouble
x [CDouble]
s1 = do
let n :: Int
n = Int
3
let nBytes :: Int
nBytes = let a :: CDouble
a = CDouble
1.0 :: CDouble in Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
* CDouble -> Int
forall a. Storable a => a -> Int
sizeOf CDouble
a
Int -> (Ptr CDouble -> IO [CDouble]) -> IO [CDouble]
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
nBytes ((Ptr CDouble -> IO [CDouble]) -> IO [CDouble])
-> (Ptr CDouble -> IO [CDouble]) -> IO [CDouble]
forall a b. (a -> b) -> a -> b
$ \Ptr CDouble
ptx -> do
[CDouble] -> (Int -> Ptr CDouble -> IO ()) -> IO ()
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [CDouble]
s1 ((Int -> Ptr CDouble -> IO ()) -> IO ())
-> (Int -> Ptr CDouble -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Int
l1 Ptr CDouble
pt1 ->
CDouble -> Ptr CDouble -> Ptr CDouble -> IO ()
c_mulScaleVec3 CDouble
x Ptr CDouble
pt1 Ptr CDouble
ptx
[CDouble]
arr <- Int -> Ptr CDouble -> IO [CDouble]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
n Ptr CDouble
ptx
[CDouble] -> IO [CDouble]
forall (m :: * -> *) a. Monad m => a -> m a
return [CDouble]
arr
f_mulVec3Scale :: [CDouble] -> CDouble -> IO [CDouble]
f_mulVec3Scale :: [CDouble] -> CDouble -> IO [CDouble]
f_mulVec3Scale [CDouble]
s1 CDouble
x = CDouble -> [CDouble] -> IO [CDouble]
f_mulScaleVec3 CDouble
x [CDouble]
s1
f_alloca_memory::Int -> IO [Int]
f_alloca_memory :: Int -> IO [Int]
f_alloca_memory Int
n = do
Int -> (Ptr CInt -> IO [Int]) -> IO [Int]
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
n ((Ptr CInt -> IO [Int]) -> IO [Int])
-> (Ptr CInt -> IO [Int]) -> IO [Int]
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
pt -> do
Ptr CInt -> CInt -> IO ()
c_alloca_memory Ptr CInt
pt (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n)
[CInt]
arr <- Int -> Ptr CInt -> IO [CInt]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
n Ptr CInt
pt
[Int] -> IO [Int]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Int] -> IO [Int]) -> [Int] -> IO [Int]
forall a b. (a -> b) -> a -> b
$ (CInt -> Int) -> [CInt] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral [CInt]
arr