- data PlatformID
- getPlatformIDs :: IO [PlatformID]
- platformProfile :: PlatformID -> String
- platformVersion :: PlatformID -> String
- platformName :: PlatformID -> String
- platformVendor :: PlatformID -> String
- platformExtensions :: PlatformID -> String
- data DeviceType
- deviceTypeAll :: [DeviceType]
- data DeviceID
- getDeviceID :: [DeviceType] -> IO DeviceID
- getDeviceIDs :: [DeviceType] -> Maybe PlatformID -> IO [DeviceID]
- data Context
- createContext :: [DeviceID] -> IO Context
- createContextFromType :: [DeviceType] -> IO Context
- contextDevices :: Context -> [DeviceID]
- setNotifier :: MonadIO m => Notifier -> m ()
- type Notifier = String -> ByteString -> IO ()
- type Size = Word64
- type ClULong = Word64
- deviceType :: DeviceID -> [DeviceType]
- deviceVendorId :: DeviceID -> ClUInt
- deviceMaxComputeUnits :: DeviceID -> ClUInt
- deviceMaxWorkItemDimensions :: DeviceID -> CUInt
- deviceMaxWorkGroupSize :: DeviceID -> Size
- deviceMaxWorkItemSizes :: DeviceID -> [Size]
- devicePreferredVectorWidthChar :: DeviceID -> ClUInt
- devicePreferredVectorWidthShort :: DeviceID -> ClUInt
- devicePreferredVectorWidthInt :: DeviceID -> ClUInt
- devicePreferredVectorWidthLong :: DeviceID -> ClUInt
- devicePreferredVectorWidthFloat :: DeviceID -> ClUInt
- devicePreferredVectorWidthDouble :: DeviceID -> ClUInt
- deviceMaxClockFrequency :: DeviceID -> ClUInt
- deviceAddressBits :: DeviceID -> ClUInt
- deviceMaxReadImageArgs :: DeviceID -> ClUInt
- deviceMaxWriteImageArgs :: DeviceID -> ClUInt
- deviceMaxMemAllocSize :: DeviceID -> CULLong
- deviceImage2dMaxWidth :: DeviceID -> Size
- deviceImage2dMaxHeight :: DeviceID -> Size
- deviceImage3dMaxWidth :: DeviceID -> Size
- deviceImage3dMaxHeight :: DeviceID -> Size
- deviceImage3dMaxDepth :: DeviceID -> Size
- deviceImageSupport :: DeviceID -> Bool
- deviceMaxParameterSize :: DeviceID -> Size
- deviceMaxSamplers :: DeviceID -> CUInt
- deviceMemBaseAddrAlign :: DeviceID -> ClUInt
- deviceMinDataTypeAlignSize :: DeviceID -> ClUInt
- deviceSingleFpConfig :: DeviceID -> [DeviceFPConfig]
- data DeviceFPConfig
- deviceGlobalMemCacheType :: DeviceID -> Maybe DeviceGlobalMemCacheType
- data DeviceGlobalMemCacheType
- deviceGlobalMemCachelineSize :: DeviceID -> CInt
- deviceGlobalMemCacheSize :: DeviceID -> ClULong
- deviceGlobalMemSize :: DeviceID -> ClULong
- deviceMaxConstantBufferSize :: DeviceID -> ClULong
- deviceMaxConstantArgs :: DeviceID -> CUInt
- deviceLocalMemType :: DeviceID -> DeviceLocalMemType
- data DeviceLocalMemType
- deviceLocalMemSize :: DeviceID -> ClULong
- deviceErrorCorrectionSupport :: DeviceID -> Bool
- deviceProfilingTimerResolution :: DeviceID -> Size
- deviceEndianLittle :: DeviceID -> Bool
- deviceAvailable :: DeviceID -> Bool
- deviceCompilerAvailable :: DeviceID -> Bool
- deviceExecutionCapabilities :: DeviceID -> [DeviceExecutionCapability]
- data DeviceExecutionCapability
- deviceQueueProperties :: DeviceID -> [CommandQueueProperty]
- deviceName :: DeviceID -> String
- deviceVendor :: DeviceID -> String
- driverVersion :: DeviceID -> String
- deviceProfile :: DeviceID -> String
- deviceVersion :: DeviceID -> String
- deviceExtensions :: DeviceID -> String
- devicePlatform :: DeviceID -> PlatformID
Platforms
data PlatformID
getPlatformIDs :: IO [PlatformID]
platformProfile :: PlatformID -> String
platformVersion :: PlatformID -> String
platformName :: PlatformID -> String
platformVendor :: PlatformID -> String
Devices
data DeviceType
deviceTypeAll :: [DeviceType]
getDeviceID :: [DeviceType] -> IO DeviceID
getDeviceIDs :: [DeviceType] -> Maybe PlatformID -> IO [DeviceID]
Contexts
data Context
createContext :: [DeviceID] -> IO Context
createContextFromType :: [DeviceType] -> IO Context
contextDevices :: Context -> [DeviceID]
setNotifier :: MonadIO m => Notifier -> m ()
Set an action to be run when an error occurs in a context.
The default is for no action to be run.
type Notifier
= String | An error string. |
-> ByteString | Binary data which can be used to log additional information (implementation-dependent). |
-> IO () |
Device properties
deviceType :: DeviceID -> [DeviceType]
deviceVendorId :: DeviceID -> ClUInt
deviceMaxComputeUnits :: DeviceID -> ClUInt
deviceMaxWorkItemSizes :: DeviceID -> [Size]
devicePreferredVectorWidthChar :: DeviceID -> ClUInt
devicePreferredVectorWidthShort :: DeviceID -> ClUInt
devicePreferredVectorWidthInt :: DeviceID -> ClUInt
devicePreferredVectorWidthLong :: DeviceID -> ClUInt
devicePreferredVectorWidthFloat :: DeviceID -> ClUInt
devicePreferredVectorWidthDouble :: DeviceID -> ClUInt
deviceMaxClockFrequency :: DeviceID -> ClUInt
deviceAddressBits :: DeviceID -> ClUInt
deviceMaxReadImageArgs :: DeviceID -> ClUInt
deviceMaxWriteImageArgs :: DeviceID -> ClUInt
deviceImageSupport :: DeviceID -> Bool
deviceMaxSamplers :: DeviceID -> CUInt
deviceMemBaseAddrAlign :: DeviceID -> ClUInt
deviceMinDataTypeAlignSize :: DeviceID -> ClUInt
data DeviceFPConfig
data DeviceLocalMemType
deviceEndianLittle :: DeviceID -> Bool
deviceAvailable :: DeviceID -> Bool
deviceName :: DeviceID -> String
deviceVendor :: DeviceID -> String
driverVersion :: DeviceID -> String
deviceProfile :: DeviceID -> String
deviceVersion :: DeviceID -> String
deviceExtensions :: DeviceID -> String
devicePlatform :: DeviceID -> PlatformID