Copyright | [2009..2018] Trevor L. McDonell |
---|---|
License | BSD |
Safe Haskell | None |
Language | Haskell98 |
Module management for low-level driver interface
Synopsis
- data JITInputType
- data JITFallback
- data JITTarget
- data JITResult = JITResult {
- jitTime :: !Float
- jitInfoLog :: !ByteString
- jitModule :: !Module
- data JITOption
- newtype Module = Module (Ptr ())
- loadFile :: FilePath -> IO Module
- loadData :: ByteString -> IO Module
- loadDataFromPtr :: Ptr Word8 -> IO Module
- loadDataEx :: ByteString -> [JITOption] -> IO JITResult
- loadDataFromPtrEx :: Ptr Word8 -> [JITOption] -> IO JITResult
- unload :: Module -> IO ()
- module Foreign.CUDA.Driver.Module.Query
Documentation
data JITInputType Source #
Device code formats that can be used for online linking
Instances
Enum JITInputType Source # | |
Defined in Foreign.CUDA.Driver.Module.Base succ :: JITInputType -> JITInputType # pred :: JITInputType -> JITInputType # toEnum :: Int -> JITInputType # fromEnum :: JITInputType -> Int # enumFrom :: JITInputType -> [JITInputType] # enumFromThen :: JITInputType -> JITInputType -> [JITInputType] # enumFromTo :: JITInputType -> JITInputType -> [JITInputType] # enumFromThenTo :: JITInputType -> JITInputType -> JITInputType -> [JITInputType] # | |
Eq JITInputType Source # | |
Defined in Foreign.CUDA.Driver.Module.Base (==) :: JITInputType -> JITInputType -> Bool # (/=) :: JITInputType -> JITInputType -> Bool # | |
Show JITInputType Source # | |
Defined in Foreign.CUDA.Driver.Module.Base showsPrec :: Int -> JITInputType -> ShowS # show :: JITInputType -> String # showList :: [JITInputType] -> ShowS # |
data JITFallback Source #
Online compilation fallback strategy
Instances
Enum JITFallback Source # | |
Defined in Foreign.CUDA.Driver.Module.Base succ :: JITFallback -> JITFallback # pred :: JITFallback -> JITFallback # toEnum :: Int -> JITFallback # fromEnum :: JITFallback -> Int # enumFrom :: JITFallback -> [JITFallback] # enumFromThen :: JITFallback -> JITFallback -> [JITFallback] # enumFromTo :: JITFallback -> JITFallback -> [JITFallback] # enumFromThenTo :: JITFallback -> JITFallback -> JITFallback -> [JITFallback] # | |
Eq JITFallback Source # | |
Defined in Foreign.CUDA.Driver.Module.Base (==) :: JITFallback -> JITFallback -> Bool # (/=) :: JITFallback -> JITFallback -> Bool # | |
Show JITFallback Source # | |
Defined in Foreign.CUDA.Driver.Module.Base showsPrec :: Int -> JITFallback -> ShowS # show :: JITFallback -> String # showList :: [JITFallback] -> ShowS # |
Online compilation target architecture
Compute20 | |
Compute21 | |
Compute30 | |
Compute32 | |
Compute35 | |
Compute37 | |
Compute50 | |
Compute52 | |
Compute53 | |
Compute60 | |
Compute61 | |
Compute62 | |
Compute70 | |
Compute75 |
Instances
Enum JITTarget Source # | |
Defined in Foreign.CUDA.Driver.Module.Base succ :: JITTarget -> JITTarget # pred :: JITTarget -> JITTarget # fromEnum :: JITTarget -> Int # enumFrom :: JITTarget -> [JITTarget] # enumFromThen :: JITTarget -> JITTarget -> [JITTarget] # enumFromTo :: JITTarget -> JITTarget -> [JITTarget] # enumFromThenTo :: JITTarget -> JITTarget -> JITTarget -> [JITTarget] # | |
Eq JITTarget Source # | |
Show JITTarget Source # | |
Results of online compilation
JITResult | |
|
Just-in-time compilation and linking options
MaxRegisters !Int | maximum number of registers per thread |
ThreadsPerBlock !Int | number of threads per block to target for |
OptimisationLevel !Int | level of optimisation to apply (1-4, default 4) |
Target !Compute | compilation target, otherwise determined from context |
FallbackStrategy !JITFallback | fallback strategy if matching cubin not found |
GenerateDebugInfo | generate debug info (-g) (requires cuda >= 5.5) |
GenerateLineInfo | generate line number information (-lineinfo) (requires cuda >= 5.5) |
Verbose | verbose log messages (requires cuda >= 5.5) |
A reference to a Module object, containing collections of device functions
loadFile :: FilePath -> IO Module Source #
Load the contents of the specified file (either a ptx or cubin file) to create a new module, and load that module into the current context.
loadData :: ByteString -> IO Module Source #
Load the contents of the given image into a new module, and load that module into the current context. The image is (typically) the contents of a cubin or PTX file.
Note that the ByteString
will be copied into a temporary staging area so
that it can be passed to C.
loadDataFromPtr :: Ptr Word8 -> IO Module Source #
As loadData
, but read the image data from the given pointer. The image is a
NULL-terminated sequence of bytes.
loadDataEx :: ByteString -> [JITOption] -> IO JITResult Source #
Load the contents of the given image into a module with online compiler
options, and load the module into the current context. The image is
(typically) the contents of a cubin or PTX file. The actual attributes of the
compiled kernel can be probed using requires
.
Note that the ByteString
will be copied into a temporary staging area so
that it can be passed to C.
loadDataFromPtrEx :: Ptr Word8 -> [JITOption] -> IO JITResult Source #
As loadDataEx
, but read the image data from the given pointer. The image is
a NULL-terminated sequence of bytes.