{-# LINE 1 "src/Foreign/CUDA/Driver/Module/Link.chs" #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE TemplateHaskell #-}
module Foreign.CUDA.Driver.Module.Link (
LinkState, JITOption(..), JITInputType(..),
create, destroy, complete,
addFile,
addData, addDataFromPtr,
) where
import qualified Foreign.C.String as C2HSImp
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp
{-# LINE 30 "src/Foreign/CUDA/Driver/Module/Link.chs" #-}
import Foreign.CUDA.Driver.Error
import Foreign.CUDA.Driver.Module.Base
import Foreign.CUDA.Internal.C2HS
import Control.Monad ( liftM )
import Foreign
import Foreign.C
import Unsafe.Coerce
import Data.ByteString.Char8 ( ByteString )
import qualified Data.ByteString.Char8 as B
newtype LinkState = LinkState { useLinkState :: ((C2HSImp.Ptr ())) }
deriving (Show)
{-# INLINEABLE create #-}
create :: [JITOption] -> IO LinkState
create !options =
let (opt,val) = unzip $ map jitOptionUnpack options
in
withArray (map cFromEnum opt) $ \p_opts ->
withArray (map unsafeCoerce val) $ \p_vals ->
resultIfOk =<< cuLinkCreate (length opt) p_opts p_vals
{-# INLINE cuLinkCreate #-}
cuLinkCreate :: (Int) -> (Ptr CInt) -> (Ptr (Ptr ())) -> IO ((Status), (LinkState))
cuLinkCreate a1 a2 a3 =
let {a1' = fromIntegral a1} in
let {a2' = id a2} in
let {a3' = id a3} in
alloca $ \a4' ->
cuLinkCreate'_ a1' a2' a3' a4' >>= \res ->
let {res' = cToEnum res} in
peekLS a4'>>= \a4'' ->
return (res', a4'')
{-# LINE 92 "src/Foreign/CUDA/Driver/Module/Link.chs" #-}
where
peekLS = liftM LinkState . peek
{-# INLINEABLE destroy #-}
destroy :: LinkState -> IO ()
destroy !s = nothingIfOk =<< cuLinkDestroy s
{-# INLINE cuLinkDestroy #-}
cuLinkDestroy :: (LinkState) -> IO ((Status))
cuLinkDestroy a1 =
let {a1' = useLinkState a1} in
cuLinkDestroy'_ a1' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 115 "src/Foreign/CUDA/Driver/Module/Link.chs" #-}
{-# INLINEABLE complete #-}
complete :: LinkState -> IO Module
complete !ls = do
cubin <- resultIfOk =<< cuLinkComplete ls nullPtr
mdl <- loadDataFromPtr (castPtr cubin)
destroy ls
return mdl
{-# INLINE cuLinkComplete #-}
cuLinkComplete :: (LinkState) -> (Ptr Int) -> IO ((Status), (Ptr ()))
cuLinkComplete a1 a3 =
let {a1' = useLinkState a1} in
alloca $ \a2' ->
let {a3' = castPtr a3} in
cuLinkComplete'_ a1' a2' a3' >>= \res ->
let {res' = cToEnum res} in
peek a2'>>= \a2'' ->
return (res', a2'')
{-# LINE 144 "src/Foreign/CUDA/Driver/Module/Link.chs" #-}
{-# INLINEABLE addFile #-}
addFile :: LinkState -> FilePath -> JITInputType -> [JITOption] -> IO ()
addFile !ls !fp !t !options =
let (opt,val) = unzip $ map jitOptionUnpack options
in
withArrayLen (map cFromEnum opt) $ \i p_opts ->
withArray (map unsafeCoerce val) $ \ p_vals ->
nothingIfOk =<< cuLinkAddFile ls t fp i p_opts p_vals
{-# INLINE cuLinkAddFile #-}
cuLinkAddFile :: (LinkState) -> (JITInputType) -> (FilePath) -> (Int) -> (Ptr CInt) -> (Ptr (Ptr ())) -> IO ((Status))
cuLinkAddFile a1 a2 a3 a4 a5 a6 =
let {a1' = useLinkState a1} in
let {a2' = cFromEnum a2} in
withCString a3 $ \a3' ->
let {a4' = fromIntegral a4} in
let {a5' = id a5} in
let {a6' = id a6} in
cuLinkAddFile'_ a1' a2' a3' a4' a5' a6' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 176 "src/Foreign/CUDA/Driver/Module/Link.chs" #-}
{-# INLINEABLE addData #-}
addData :: LinkState -> ByteString -> JITInputType -> [JITOption] -> IO ()
addData !ls !img !k !options =
B.useAsCStringLen img (\(p, n) -> addDataFromPtr ls n (castPtr p) k options)
{-# INLINEABLE addDataFromPtr #-}
addDataFromPtr :: LinkState -> Int -> Ptr Word8 -> JITInputType -> [JITOption] -> IO ()
addDataFromPtr !ls !n !img !t !options =
let (opt,val) = unzip $ map jitOptionUnpack options
in
withArrayLen (map cFromEnum opt) $ \i p_opts ->
withArray (map unsafeCoerce val) $ \ p_vals ->
nothingIfOk =<< cuLinkAddData ls t img n "<unknown>" i p_opts p_vals
{-# INLINE cuLinkAddData #-}
cuLinkAddData :: (LinkState) -> (JITInputType) -> (Ptr Word8) -> (Int) -> (String) -> (Int) -> (Ptr CInt) -> (Ptr (Ptr ())) -> IO ((Status))
cuLinkAddData a1 a2 a3 a4 a5 a6 a7 a8 =
let {a1' = useLinkState a1} in
let {a2' = cFromEnum a2} in
let {a3' = castPtr a3} in
let {a4' = fromIntegral a4} in
C2HSImp.withCString a5 $ \a5' ->
let {a6' = fromIntegral a6} in
let {a7' = id a7} in
let {a8' = id a8} in
cuLinkAddData'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 223 "src/Foreign/CUDA/Driver/Module/Link.chs" #-}
foreign import ccall unsafe "Foreign/CUDA/Driver/Module/Link.chs.h cuLinkCreate"
cuLinkCreate'_ :: (C2HSImp.CUInt -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr (C2HSImp.Ptr ())) -> ((C2HSImp.Ptr (C2HSImp.Ptr ())) -> (IO C2HSImp.CInt)))))
foreign import ccall unsafe "Foreign/CUDA/Driver/Module/Link.chs.h cuLinkDestroy"
cuLinkDestroy'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall unsafe "Foreign/CUDA/Driver/Module/Link.chs.h cuLinkComplete"
cuLinkComplete'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr (C2HSImp.Ptr ())) -> ((C2HSImp.Ptr C2HSImp.CULong) -> (IO C2HSImp.CInt))))
foreign import ccall unsafe "Foreign/CUDA/Driver/Module/Link.chs.h cuLinkAddFile"
cuLinkAddFile'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr (C2HSImp.Ptr ())) -> (IO C2HSImp.CInt)))))))
foreign import ccall unsafe "Foreign/CUDA/Driver/Module/Link.chs.h cuLinkAddData"
cuLinkAddData'_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr (C2HSImp.Ptr ())) -> (IO C2HSImp.CInt)))))))))