{-# LINE 1 "src/Sys/DL.chs" #-}
{-# LANGUAGE OverloadedStrings #-}
module Sys.DL ( CCtx, MCtx, libc, mem', math' ) where
import Data.Functor (($>))
import Foreign.C.Types (CSize)
import Data.Int (Int32)
import Foreign.Ptr (FunPtr, IntPtr (..), Ptr, castFunPtrToPtr, ptrToIntPtr)
import System.Posix.DynamicLinker.ByteString (DL, RTLDFlags (RTLD_LAZY), dlclose, dlopen, dlsym)
type CCtx = (Int, Int, Int, Int); type MCtx = (Int, Int, Int)
math' :: IO MCtx
math' :: IO MCtx
math' = do {(e,l,p) <- IO
(FunPtr (Double -> Double), FunPtr (Double -> Double),
FunPtr (Double -> Double -> Double))
math; pure (ip e, ip l, ip p)}
mem' :: IO CCtx
mem' :: IO CCtx
mem' = do {(m,f,xr,r) <- IO
(FunPtr (CSize -> IO (Ptr Any)), FunPtr (Ptr Any -> IO ()),
FunPtr (IO Double), FunPtr (IO Int32))
forall a.
IO
(FunPtr (CSize -> IO (Ptr a)), FunPtr (Ptr a -> IO ()),
FunPtr (IO Double), FunPtr (IO Int32))
mem; pure (ip m, ip f, ip xr, ip r)}
ip :: FunPtr a -> Int
ip = (\(IntPtr Int
i) -> Int
i) (IntPtr -> Int) -> (FunPtr a -> IntPtr) -> FunPtr a -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Any -> IntPtr
forall a. Ptr a -> IntPtr
ptrToIntPtr (Ptr Any -> IntPtr) -> (FunPtr a -> Ptr Any) -> FunPtr a -> IntPtr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunPtr a -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr
mem :: IO (FunPtr (CSize -> IO (Ptr a)), FunPtr (Ptr a -> IO ()), FunPtr (IO Double), FunPtr (IO Int32))
mem :: forall a.
IO
(FunPtr (CSize -> IO (Ptr a)), FunPtr (Ptr a -> IO ()),
FunPtr (IO Double), FunPtr (IO Int32))
mem = do {c <- IO DL
libc; m <- dlsym c "malloc"; f <- dlsym c "free"; xr <- dlsym c "drand48"; r <- dlsym c "lrand48"; dlclose c$>(m,f,xr,r)}
math :: IO (FunPtr (Double -> Double), FunPtr (Double -> Double), FunPtr (Double -> Double -> Double))
math :: IO
(FunPtr (Double -> Double), FunPtr (Double -> Double),
FunPtr (Double -> Double -> Double))
math = do {m <- IO DL
libm; e <- dlsym m "exp"; l <- dlsym m "log"; p <- dlsym m "pow"; dlclose m$>(e,l,p)}
ll :: RawFilePath -> IO DL
ll RawFilePath
p = RawFilePath -> [RTLDFlags] -> IO DL
dlopen RawFilePath
p [RTLDFlags
RTLD_LAZY]
libc, libm :: IO DL
libc :: IO DL
libc = RawFilePath -> IO DL
ll RawFilePath
"libc.dylib"
libm :: IO DL
libm = RawFilePath -> IO DL
ll RawFilePath
"libm.dylib"