-- GENERATED by C->Haskell Compiler, version 0.16.0 Crystal Seed, 24 Jan 2009 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "src/System/GPU/OpenCL/Types.chs" #-}{- Copyright (c) 2011 Luis Cabellos,

All rights reserved.

Redistribution and use in source and binary forms, with or without
modification, are permitted provided that the following conditions are met:

    * Redistributions of source code must retain the above copyright
      notice, this list of conditions and the following disclaimer.

    * Redistributions in binary form must reproduce the above
      copyright notice, this list of conditions and the following
      disclaimer in the documentation and/or other materials provided
      with the distribution.

    * Neither the name of  nor the names of other
      contributors may be used to endorse or promote products derived
      from this software without specific prior written permission.

THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
-}
{-# LANGUAGE DeriveDataTypeable #-}
module System.GPU.OpenCL.Types( 
  -- * Symple CL Types
  CLbool, CLint, CLuint, CLulong, CLProgram, CLEvent, CLMem, CLPlatformID, 
  CLDeviceID, CLContext, CLCommandQueue, CLPlatformInfo_, CLDeviceType_, 
  CLDeviceInfo_, CLContextInfo_, CLContextProperty_, CLCommandQueueInfo_, 
  CLEventInfo_, CLProfilingInfo_, CLCommandType_, CLCommandQueueProperty_, 
  CLMemFlags_, CLImageFormat_p, CLMemObjectType_, CLMemInfo_, CLImageInfo_,
  CLProgramInfo_, CLBuildStatus_,CLKernel, CLProgramBuildInfo_, CLKernelInfo_,
  CLKernelWorkGroupInfo_, CLDeviceLocalMemType_, CLDeviceMemCacheType_,
  CLSampler, CLFilterMode_, CLSamplerInfo_, CLAddressingMode_,
  -- * High Level Types
  CLError(..), CLDeviceFPConfig(..), CLDeviceMemCacheType(..), 
  CLDeviceExecCapability(..), CLDeviceLocalMemType(..), CLDeviceType(..), 
  CLCommandQueueProperty(..), CLCommandType(..),  CLCommandExecutionStatus(..), 
  CLProfilingInfo(..), CLPlatformInfo(..), CLMemFlag(..), CLMemObjectType(..),
  CLBuildStatus(..), CLAddressingMode(..), CLFilterMode(..),
  -- * Functions
  wrapPError, wrapCheckSuccess, wrapGetInfo, whenSuccess, getCLValue, 
  throwCLError, getEnumCL, bitmaskToFlags, getCommandExecutionStatus, 
  bitmaskToDeviceTypes, bitmaskFromFlags, bitmaskToCommandQueueProperties, 
  bitmaskToFPConfig, bitmaskToExecCapability, bitmaskToMemFlags )
       where

-- -----------------------------------------------------------------------------
import Foreign
import Foreign.C.Types
import Data.List( foldl' )
import Data.Typeable( Typeable(..) )
import Control.Applicative( (<$>) )
import Control.Exception( Exception(..), throwIO )


-- -----------------------------------------------------------------------------

type CLPlatformID = ((Ptr ()))
{-# LINE 68 "src/System/GPU/OpenCL/Types.chs" #-}
type CLDeviceID = ((Ptr ()))
{-# LINE 69 "src/System/GPU/OpenCL/Types.chs" #-}
type CLContext = ((Ptr ()))
{-# LINE 70 "src/System/GPU/OpenCL/Types.chs" #-}
type CLCommandQueue = ((Ptr ()))
{-# LINE 71 "src/System/GPU/OpenCL/Types.chs" #-}
type CLMem = ((Ptr ()))
{-# LINE 72 "src/System/GPU/OpenCL/Types.chs" #-}
type CLEvent = ((Ptr ()))
{-# LINE 73 "src/System/GPU/OpenCL/Types.chs" #-}
type CLProgram = ((Ptr ()))
{-# LINE 74 "src/System/GPU/OpenCL/Types.chs" #-}
type CLKernel = ((Ptr ()))
{-# LINE 75 "src/System/GPU/OpenCL/Types.chs" #-}
type CLSampler = ((Ptr ()))
{-# LINE 76 "src/System/GPU/OpenCL/Types.chs" #-}

type CLint = (CInt)
{-# LINE 78 "src/System/GPU/OpenCL/Types.chs" #-}
type CLuint = (CUInt)
{-# LINE 79 "src/System/GPU/OpenCL/Types.chs" #-}
type CLulong = (CULLong)
{-# LINE 80 "src/System/GPU/OpenCL/Types.chs" #-}
type CLbool = (CUInt)
{-# LINE 81 "src/System/GPU/OpenCL/Types.chs" #-}

type CLPlatformInfo_ = (CUInt)
{-# LINE 83 "src/System/GPU/OpenCL/Types.chs" #-}
type CLDeviceType_ = (CULLong)
{-# LINE 84 "src/System/GPU/OpenCL/Types.chs" #-}
type CLDeviceInfo_ = (CUInt)
{-# LINE 85 "src/System/GPU/OpenCL/Types.chs" #-}
type CLDeviceFPConfig_ = (CULLong)
{-# LINE 86 "src/System/GPU/OpenCL/Types.chs" #-}
type CLDeviceMemCacheType_ = (CUInt)
{-# LINE 87 "src/System/GPU/OpenCL/Types.chs" #-}
type CLDeviceLocalMemType_ = (CUInt)
{-# LINE 88 "src/System/GPU/OpenCL/Types.chs" #-}
type CLDeviceExecCapability_ = (CULLong)
{-# LINE 89 "src/System/GPU/OpenCL/Types.chs" #-}
type CLContextInfo_ = (CUInt)
{-# LINE 90 "src/System/GPU/OpenCL/Types.chs" #-}
type CLContextProperty_ = (CInt)
{-# LINE 91 "src/System/GPU/OpenCL/Types.chs" #-}
type CLCommandQueueInfo_ = (CUInt)
{-# LINE 92 "src/System/GPU/OpenCL/Types.chs" #-}
type CLCommandQueueProperty_ = (CULLong)
{-# LINE 93 "src/System/GPU/OpenCL/Types.chs" #-}
type CLEventInfo_ = (CUInt)
{-# LINE 94 "src/System/GPU/OpenCL/Types.chs" #-}
type CLProfilingInfo_ = (CUInt)
{-# LINE 95 "src/System/GPU/OpenCL/Types.chs" #-}
type CLCommandType_ = (CUInt)
{-# LINE 96 "src/System/GPU/OpenCL/Types.chs" #-}
type CLMemFlags_ = (CULLong)
{-# LINE 97 "src/System/GPU/OpenCL/Types.chs" #-}
type CLMemObjectType_ = (CUInt)
{-# LINE 98 "src/System/GPU/OpenCL/Types.chs" #-}
type CLMemInfo_ = (CUInt)
{-# LINE 99 "src/System/GPU/OpenCL/Types.chs" #-}
type CLImageInfo_ = (CUInt)
{-# LINE 100 "src/System/GPU/OpenCL/Types.chs" #-}
type CLProgramInfo_ = (CUInt)
{-# LINE 101 "src/System/GPU/OpenCL/Types.chs" #-}
type CLProgramBuildInfo_ = (CUInt)
{-# LINE 102 "src/System/GPU/OpenCL/Types.chs" #-}
type CLBuildStatus_ = (CInt)
{-# LINE 103 "src/System/GPU/OpenCL/Types.chs" #-}
type CLKernelInfo_ = (CUInt)
{-# LINE 104 "src/System/GPU/OpenCL/Types.chs" #-}
type CLKernelWorkGroupInfo_ = (CUInt)
{-# LINE 105 "src/System/GPU/OpenCL/Types.chs" #-}
type CLFilterMode_ = (CUInt)
{-# LINE 106 "src/System/GPU/OpenCL/Types.chs" #-}
type CLSamplerInfo_ = (CUInt)
{-# LINE 107 "src/System/GPU/OpenCL/Types.chs" #-}
type CLAddressingMode_ = (CUInt)
{-# LINE 108 "src/System/GPU/OpenCL/Types.chs" #-}

type CLImageFormat_p = Ptr (())
{-# LINE 110 "src/System/GPU/OpenCL/Types.chs" #-}

--type CLImageChannelOrder_ = {#type cl_channel_order#}
--type CLImageChannelDataType_ = {#type cl_channel_type#}

-- -----------------------------------------------------------------------------
{-| 
 * 'CL_BUILD_PROGRAM_FAILURE', Returned if there is a failure to build the
program executable.

 * 'CL_COMPILER_NOT_AVAILABLE', Returned if the parameter program is created with
'clCreateProgramWithSource' and a compiler is not available. For example
'clDeviceCompilerAvalaible' is set to 'False'.

 * 'CL_DEVICE_NOT_AVAILABLE', Returned if the specified device is not currently
available.

 * 'CL_DEVICE_NOT_FOUND', Returned if no OpenCL devices that match the specified
devices were found.

 * 'CL_IMAGE_FORMAT_MISMATCH', Returned if the specified source and destination
images are not valid image objects.

 * 'CL_IMAGE_FORMAT_NOT_SUPPORTED', Returned if the specified image format is not
supported.

 * 'CL_INVALID_ARG_INDEX', Returned if an invalid argument index is specified.

 * 'CL_INVALID_ARG_SIZE', Returned if argument size specified (arg_size) does not
match the size of the data type for an argument that is not a memory object, or
if the argument is a memory object and arg_size != sizeof(cl_mem) or if arg_size
is zero and the argument is declared with the __local qualifier or if the
argument is a sampler and arg_size != sizeof(cl_sampler).

 * 'CL_INVALID_ARG_VALUE', Returned if the argument value specified is NULL for
an argument that is not declared with the __local qualifier or vice-versa.

 * 'CL_INVALID_BINARY', Returned if the program binary is not a valid binary for
the specified device.

 * 'CL_INVALID_BUFFER_SIZE', Returned if the value of the parameter size is 0 or
is greater than 'clDeviceMaxMemAllocSize' for all devices specified in the
parameter context.

 * 'CL_INVALID_BUILD_OPTIONS', Returned if the specified build options are
invalid.

 * 'CL_INVALID_COMMAND_QUEUE', Returned if the specified command-queue is not a
valid command-queue.

 * 'CL_INVALID_CONTEXT', Returned if the specified context is not a valid OpenCL
context, or the context associated with certain parameters are not the same.

 * 'CL_INVALID_DEVICE', Returned if the device or devices specified are not
valid.

 * 'CL_INVALID_DEVICE_TYPE', Returned if device type specified is not valid.

 * 'CL_INVALID_EVENT', Returned if the event objects specified are not valid.

 * 'CL_INVALID_EVENT_WAIT_LIST', Returned if event_wait_list is NULL and
num_events_in_wait_list > 0, or event_wait_list_list is not NULL and
num_events_in_wait_list is 0, or specified event objects are not valid events.

 * 'CL_INVALID_GL_OBJECT', Returned if obj is not a vaild GL object or is a GL
object but does not have an existing data store.

 * 'CL_INVALID_GLOBAL_OFFSET', Returned if global_work_offset is not NULL.

 * 'CL_INVALID_HOST_PTR', Returned if host_ptr is NULL and 'CL_MEM_USE_HOST_PTR'
or 'CL_MEM_COPY_HOST_PTR' are set in flags or if host_ptr is not NULL but
'CL_MEM_COPY_HOST_PTR' or 'CL_MEM_USE_HOST_PTR' are not set in flags.

 * 'CL_INVALID_IMAGE_FORMAT_DESCRIPTOR', Returned if the image format specified
is not valid or is NULL or does not map to a supported OpenCL image format.

 * 'CL_INVALID_IMAGE_SIZE', Returned if the specified image width or height are
invalid or if the image row pitch and image slice pitch do not follow the rules.

 * 'CL_INVALID_KERNEL_NAME', Returned if the specified kernel name is not found
in program.

 * 'CL_INVALID_KERNEL', Returned if the specified kernel is not a valid kernel
object.

 * 'CL_INVALID_KERNEL_ARGS', Returned if the kernel argument values have not been
specified.

 * 'CL_INVALID_KERNEL_DEFINITION', Returned if the function definition for
__kernel function given by kernel_name such as the number of arguments, the
argument types are not the same for all devices for which the program executable
has been built.

 * 'CL_INVALID_MEM_OBJECT', Returned if a parameter is not a valid memory, image,
or buffer object.

 * 'CL_INVALID_OPERATION', Returned if there are no devices in context that
support images. Returned if the build of a program executable for any of the
devices specified by a previous call to 'clBuildProgram' for program has not
completed, or if there are kernel objects attached to program. Returned by
'clEnqueueNativeKernel' if the specified device cannot execute the native
kernel.

 * 'CL_INVALID_PLATFORM', Returned if the specified platform is not a valid
platform, or no platform could be selected, or if platform value specified in
properties is not a valid platform.

 * 'CL_INVALID_PROGRAM', Returned if the specified program is not a valid program
object.

 * 'CL_INVALID_PROGRAM_EXECUTABLE', Returned if there is no successfully built
executable for program, or if there is no device in program. Returned if there
is no successfully built program executable available for device associated with
command_queue.

 * 'CL_INVALID_QUEUE_PROPERTIES', Returned if specified properties are valid but
are not supported by the device.

 * 'CL_INVALID_SAMPLER', Returned if the specified sampler is not a valid sampler
object, or for an argument declared to be of type sampler_t when the specified
arg_value is not a valid sampler object.

 * 'CL_INVALID_VALUE', Returned if a parameter is not an expected value.

 * 'CL_INVALID_WORK_DIMENSION', Returned if work_dim is not a valid value.

 * 'CL_INVALID_WORK_GROUP_SIZE', Returned if local_work_size is specified and
number of workitems specified by global_work_size is not evenly divisible by
size of work-group given by local_work_size or does not match the work-group
size specified for kernel using the __attribute__((reqd_work_group_size(X, Y,
Z))) qualifier in program source.

 * 'CL_INVALID_WORK_ITEM_SIZE', Returned if the number of work-items specified in
any of local_work_size... [0]... local_work_size[work_dim - 1] is greater than
the corresponding values specified by 'clDeviceMaxWorkItemSizes'.

 * 'CL_MAP_FAILURE', Returned by if there is a failure to map the requested
region into the host address space. This error cannot occur for buffer objects
created with 'CLMEM_USE_HOST_PTR' or 'CLMEM_ALLOC_HOST_PTR'.

 * 'CL_MEM_OBJECT_ALLOCATION_FAILURE', Returned if there is a failure to allocate
memory for data store associated with image or buffer objects specified as
arguments to kernel.

 * 'CL_MEM_COPY_OVERLAP', Returned if the source and destination images are the
same image (or the source and destination buffers are the same buffer), and the
source and destination regions overlap.

 * 'CL_OUT_OF_HOST_MEMORY', Returned in the event of a failure to allocate
resources required by the OpenCL implementation on the host.

 * 'CL_OUT_OF_RESOURCES', Returned in the event of a failure to queue the
execution instance of kernel on the command-queue because of insufficient
resources needed to execute the kernel.

 * 'CL_PROFILING_INFO_NOT_AVAILABLE', Returned if the 'CL_QUEUE_PROFILING_ENABLE'
flag is not set for the command-queue and the profiling information is currently
not available (because the command identified by event has not completed).

 * 'CL_SUCCESS', Indicates that the function executed successfully.
-}
data CLError = CL_BUILD_PROGRAM_FAILURE
             | CL_COMPILER_NOT_AVAILABLE
             | CL_DEVICE_NOT_AVAILABLE
             | CL_DEVICE_NOT_FOUND
             | CL_IMAGE_FORMAT_MISMATCH
             | CL_IMAGE_FORMAT_NOT_SUPPORTED
             | CL_INVALID_ARG_INDEX
             | CL_INVALID_ARG_SIZE
             | CL_INVALID_ARG_VALUE
             | CL_INVALID_BINARY
             | CL_INVALID_BUFFER_SIZE
             | CL_INVALID_BUILD_OPTIONS
             | CL_INVALID_COMMAND_QUEUE
             | CL_INVALID_CONTEXT
             | CL_INVALID_DEVICE
             | CL_INVALID_DEVICE_TYPE
             | CL_INVALID_EVENT
             | CL_INVALID_EVENT_WAIT_LIST
             | CL_INVALID_GL_OBJECT
             | CL_INVALID_GLOBAL_OFFSET
             | CL_INVALID_HOST_PTR
             | CL_INVALID_IMAGE_FORMAT_DESCRIPTOR
             | CL_INVALID_IMAGE_SIZE
             | CL_INVALID_KERNEL_NAME
             | CL_INVALID_KERNEL
             | CL_INVALID_KERNEL_ARGS
             | CL_INVALID_KERNEL_DEFINITION
             | CL_INVALID_MEM_OBJECT
             | CL_INVALID_OPERATION
             | CL_INVALID_PLATFORM
             | CL_INVALID_PROGRAM
             | CL_INVALID_PROGRAM_EXECUTABLE
             | CL_INVALID_QUEUE_PROPERTIES
             | CL_INVALID_SAMPLER
             | CL_INVALID_VALUE
             | CL_INVALID_WORK_DIMENSION
             | CL_INVALID_WORK_GROUP_SIZE
             | CL_INVALID_WORK_ITEM_SIZE
             | CL_MAP_FAILURE
             | CL_MEM_OBJECT_ALLOCATION_FAILURE
             | CL_MEM_COPY_OVERLAP
             | CL_OUT_OF_HOST_MEMORY
             | CL_OUT_OF_RESOURCES
             | CL_PROFILING_INFO_NOT_AVAILABLE
             | CL_SUCCESS
             deriving (Show,Eq,Typeable)
instance Enum CLError where
  fromEnum CL_BUILD_PROGRAM_FAILURE = (-11)
  fromEnum CL_COMPILER_NOT_AVAILABLE = (-3)
  fromEnum CL_DEVICE_NOT_AVAILABLE = (-2)
  fromEnum CL_DEVICE_NOT_FOUND = (-1)
  fromEnum CL_IMAGE_FORMAT_MISMATCH = (-9)
  fromEnum CL_IMAGE_FORMAT_NOT_SUPPORTED = (-10)
  fromEnum CL_INVALID_ARG_INDEX = (-49)
  fromEnum CL_INVALID_ARG_SIZE = (-51)
  fromEnum CL_INVALID_ARG_VALUE = (-50)
  fromEnum CL_INVALID_BINARY = (-42)
  fromEnum CL_INVALID_BUFFER_SIZE = (-61)
  fromEnum CL_INVALID_BUILD_OPTIONS = (-43)
  fromEnum CL_INVALID_COMMAND_QUEUE = (-36)
  fromEnum CL_INVALID_CONTEXT = (-34)
  fromEnum CL_INVALID_DEVICE = (-33)
  fromEnum CL_INVALID_DEVICE_TYPE = (-31)
  fromEnum CL_INVALID_EVENT = (-58)
  fromEnum CL_INVALID_EVENT_WAIT_LIST = (-57)
  fromEnum CL_INVALID_GL_OBJECT = (-60)
  fromEnum CL_INVALID_GLOBAL_OFFSET = (-56)
  fromEnum CL_INVALID_HOST_PTR = (-37)
  fromEnum CL_INVALID_IMAGE_FORMAT_DESCRIPTOR = (-39)
  fromEnum CL_INVALID_IMAGE_SIZE = (-40)
  fromEnum CL_INVALID_KERNEL_NAME = (-46)
  fromEnum CL_INVALID_KERNEL = (-48)
  fromEnum CL_INVALID_KERNEL_ARGS = (-52)
  fromEnum CL_INVALID_KERNEL_DEFINITION = (-47)
  fromEnum CL_INVALID_MEM_OBJECT = (-38)
  fromEnum CL_INVALID_OPERATION = (-59)
  fromEnum CL_INVALID_PLATFORM = (-32)
  fromEnum CL_INVALID_PROGRAM = (-44)
  fromEnum CL_INVALID_PROGRAM_EXECUTABLE = (-45)
  fromEnum CL_INVALID_QUEUE_PROPERTIES = (-35)
  fromEnum CL_INVALID_SAMPLER = (-41)
  fromEnum CL_INVALID_VALUE = (-30)
  fromEnum CL_INVALID_WORK_DIMENSION = (-53)
  fromEnum CL_INVALID_WORK_GROUP_SIZE = (-54)
  fromEnum CL_INVALID_WORK_ITEM_SIZE = (-55)
  fromEnum CL_MAP_FAILURE = (-12)
  fromEnum CL_MEM_OBJECT_ALLOCATION_FAILURE = (-4)
  fromEnum CL_MEM_COPY_OVERLAP = (-8)
  fromEnum CL_OUT_OF_HOST_MEMORY = (-6)
  fromEnum CL_OUT_OF_RESOURCES = (-5)
  fromEnum CL_PROFILING_INFO_NOT_AVAILABLE = (-7)
  fromEnum CL_SUCCESS = 0

  toEnum (-11) = CL_BUILD_PROGRAM_FAILURE
  toEnum (-3) = CL_COMPILER_NOT_AVAILABLE
  toEnum (-2) = CL_DEVICE_NOT_AVAILABLE
  toEnum (-1) = CL_DEVICE_NOT_FOUND
  toEnum (-9) = CL_IMAGE_FORMAT_MISMATCH
  toEnum (-10) = CL_IMAGE_FORMAT_NOT_SUPPORTED
  toEnum (-49) = CL_INVALID_ARG_INDEX
  toEnum (-51) = CL_INVALID_ARG_SIZE
  toEnum (-50) = CL_INVALID_ARG_VALUE
  toEnum (-42) = CL_INVALID_BINARY
  toEnum (-61) = CL_INVALID_BUFFER_SIZE
  toEnum (-43) = CL_INVALID_BUILD_OPTIONS
  toEnum (-36) = CL_INVALID_COMMAND_QUEUE
  toEnum (-34) = CL_INVALID_CONTEXT
  toEnum (-33) = CL_INVALID_DEVICE
  toEnum (-31) = CL_INVALID_DEVICE_TYPE
  toEnum (-58) = CL_INVALID_EVENT
  toEnum (-57) = CL_INVALID_EVENT_WAIT_LIST
  toEnum (-60) = CL_INVALID_GL_OBJECT
  toEnum (-56) = CL_INVALID_GLOBAL_OFFSET
  toEnum (-37) = CL_INVALID_HOST_PTR
  toEnum (-39) = CL_INVALID_IMAGE_FORMAT_DESCRIPTOR
  toEnum (-40) = CL_INVALID_IMAGE_SIZE
  toEnum (-46) = CL_INVALID_KERNEL_NAME
  toEnum (-48) = CL_INVALID_KERNEL
  toEnum (-52) = CL_INVALID_KERNEL_ARGS
  toEnum (-47) = CL_INVALID_KERNEL_DEFINITION
  toEnum (-38) = CL_INVALID_MEM_OBJECT
  toEnum (-59) = CL_INVALID_OPERATION
  toEnum (-32) = CL_INVALID_PLATFORM
  toEnum (-44) = CL_INVALID_PROGRAM
  toEnum (-45) = CL_INVALID_PROGRAM_EXECUTABLE
  toEnum (-35) = CL_INVALID_QUEUE_PROPERTIES
  toEnum (-41) = CL_INVALID_SAMPLER
  toEnum (-30) = CL_INVALID_VALUE
  toEnum (-53) = CL_INVALID_WORK_DIMENSION
  toEnum (-54) = CL_INVALID_WORK_GROUP_SIZE
  toEnum (-55) = CL_INVALID_WORK_ITEM_SIZE
  toEnum (-12) = CL_MAP_FAILURE
  toEnum (-4) = CL_MEM_OBJECT_ALLOCATION_FAILURE
  toEnum (-8) = CL_MEM_COPY_OVERLAP
  toEnum (-6) = CL_OUT_OF_HOST_MEMORY
  toEnum (-5) = CL_OUT_OF_RESOURCES
  toEnum (-7) = CL_PROFILING_INFO_NOT_AVAILABLE
  toEnum 0 = CL_SUCCESS
  toEnum unmatched = error ("CLError.toEnum: Cannot match " ++ show unmatched)

{-# LINE 321 "src/System/GPU/OpenCL/Types.chs" #-}

instance Exception CLError

throwCLError :: CLint -> IO a
throwCLError = throwIO . (getEnumCL :: CLint -> CLError)

wrapPError :: (Ptr CLint -> IO a) -> IO a
wrapPError f = alloca $ \perr -> do
  v <- f perr
  errcode <- getEnumCL <$> peek perr
  if errcode == CL_SUCCESS
    then return v
    else throwIO errcode
  
wrapCheckSuccess :: IO CLint -> IO Bool
wrapCheckSuccess f = f >>= return . (==CL_SUCCESS) . getEnumCL

wrapGetInfo :: Storable a 
               => (Ptr a -> Ptr CSize -> IO CLint) -> (a -> b) -> IO b
wrapGetInfo fget fconvert= alloca $ \dat -> do
  errcode <- fget dat nullPtr
  if errcode == getCLValue CL_SUCCESS
    then fmap fconvert $ peek dat
    else throwCLError errcode

whenSuccess :: IO CLint -> IO a -> IO a
whenSuccess fcheck fval = do
  errcode <- fcheck
  if errcode == getCLValue CL_SUCCESS
    then fval
    else throwCLError errcode
         
-- -----------------------------------------------------------------------------
{-|
 * 'CL_PLATFORM_PROFILE', OpenCL profile string. Returns the profile name 
supported by the implementation. The profile name returned can be one of the 
following strings:

 [@FULL_PROFILE@] If the implementation supports the OpenCL specification
(functionality defined as part of the core specification and does not require
any extensions to be supported).

 [@EMBEDDED_PROFILE@] If the implementation supports the OpenCL embedded 
profile. The embedded profile is  defined to be a subset for each version of 
OpenCL.

 * 'CL_PLATFORM_VERSION', OpenCL version string. Returns the OpenCL version 
supported by the implementation. This version string has the following format: 
/OpenCL major_version.minor_version platform-specific information/ The 
/major_version.minor_version/ value returned will be 1.0.
                    
 * 'CL_PLATFORM_NAME', Platform name string.
 
 * 'CL_PLATFORM_VENDOR', Platform vendor string.
                   
 * 'CL_PLATFORM_EXTENSIONS', Returns a space-separated list of extension names 
(the extension names themselves do not contain any spaces) supported by the 
platform. Extensions defined here must be supported by all devices associated 
with this platform.
-}
data CLPlatformInfo = CL_PLATFORM_PROFILE
                    | CL_PLATFORM_VERSION
                    | CL_PLATFORM_NAME
                    | CL_PLATFORM_VENDOR
                    | CL_PLATFORM_EXTENSIONS
                    deriving (Show)
instance Enum CLPlatformInfo where
  fromEnum CL_PLATFORM_PROFILE = 2304
  fromEnum CL_PLATFORM_VERSION = 2305
  fromEnum CL_PLATFORM_NAME = 2306
  fromEnum CL_PLATFORM_VENDOR = 2307
  fromEnum CL_PLATFORM_EXTENSIONS = 2308

  toEnum 2304 = CL_PLATFORM_PROFILE
  toEnum 2305 = CL_PLATFORM_VERSION
  toEnum 2306 = CL_PLATFORM_NAME
  toEnum 2307 = CL_PLATFORM_VENDOR
  toEnum 2308 = CL_PLATFORM_EXTENSIONS
  toEnum unmatched = error ("CLPlatformInfo.toEnum: Cannot match " ++ show unmatched)

{-# LINE 392 "src/System/GPU/OpenCL/Types.chs" #-}

-- -----------------------------------------------------------------------------
{-|
 * 'CL_DEVICE_TYPE_CPU', An OpenCL device that is the host processor. The host 
processor runs the OpenCL implementations and is a single or multi-core CPU.
                  
 * 'CL_DEVICE_TYPE_GPU', An OpenCL device that is a GPU. By this we mean that the 
device can also be used to accelerate a 3D API such as OpenGL or DirectX.
                  
 * 'CL_DEVICE_TYPE_ACCELERATOR', Dedicated OpenCL accelerators (for example the 
IBM CELL Blade). These devices communicate with the host processor using a 
peripheral interconnect such as PCIe.
                
 * 'CL_DEVICE_TYPE_DEFAULT', The default OpenCL device in the system.
           
 * 'CL_DEVICE_TYPE_ALL', All OpenCL devices available in the system.
-}
data CLDeviceType = CL_DEVICE_TYPE_CPU
                  | CL_DEVICE_TYPE_GPU
                  | CL_DEVICE_TYPE_ACCELERATOR
                  | CL_DEVICE_TYPE_DEFAULT
                  | CL_DEVICE_TYPE_ALL
                  deriving (Show)
instance Enum CLDeviceType where
  fromEnum CL_DEVICE_TYPE_CPU = 2
  fromEnum CL_DEVICE_TYPE_GPU = 4
  fromEnum CL_DEVICE_TYPE_ACCELERATOR = 8
  fromEnum CL_DEVICE_TYPE_DEFAULT = 1
  fromEnum CL_DEVICE_TYPE_ALL = 4294967295

  toEnum 2 = CL_DEVICE_TYPE_CPU
  toEnum 4 = CL_DEVICE_TYPE_GPU
  toEnum 8 = CL_DEVICE_TYPE_ACCELERATOR
  toEnum 1 = CL_DEVICE_TYPE_DEFAULT
  toEnum 4294967295 = CL_DEVICE_TYPE_ALL
  toEnum unmatched = error ("CLDeviceType.toEnum: Cannot match " ++ show unmatched)

{-# LINE 420 "src/System/GPU/OpenCL/Types.chs" #-}

{-|
 * 'CL_QUEUE_OUT_OF_ORDER_EXEC_MODE_ENABLE', Determines whether the commands 
queued in the command-queue are executed in-order or out-of-order. If set, the 
commands in the command-queue are executed out-of-order. Otherwise, commands are 
executed in-order.
                            
 * 'CL_QUEUE_PROFILING_ENABLE', Enable or disable profiling of commands in the 
command-queue. If set, the profiling of commands is enabled. Otherwise profiling 
of commands is disabled. See 'clGetEventProfilingInfo' for more information.
-}
data CLCommandQueueProperty = CL_QUEUE_OUT_OF_ORDER_EXEC_MODE_ENABLE
                            | CL_QUEUE_PROFILING_ENABLE
                            deriving (Show,Bounded,Eq,Ord)
instance Enum CLCommandQueueProperty where
  fromEnum CL_QUEUE_OUT_OF_ORDER_EXEC_MODE_ENABLE = 1
  fromEnum CL_QUEUE_PROFILING_ENABLE = 2

  toEnum 1 = CL_QUEUE_OUT_OF_ORDER_EXEC_MODE_ENABLE
  toEnum 2 = CL_QUEUE_PROFILING_ENABLE
  toEnum unmatched = error ("CLCommandQueueProperty.toEnum: Cannot match " ++ show unmatched)

{-# LINE 439 "src/System/GPU/OpenCL/Types.chs" #-}

{-|
 * 'CL_FP_DENORM', denorms are supported.
                      
 * 'CL_FP_INF_NAN', INF and NaNs are supported.
                      
 * 'CL_FP_ROUND_TO_NEAREST', round to nearest even rounding mode supported.
                      
 * 'CL_FP_ROUND_TO_ZERO', round to zero rounding mode supported.
                      
 * 'CL_FP_ROUND_TO_INF', round to +ve and -ve infinity rounding modes supported.
                      
 * 'CL_FP_FMA', IEEE754-2008 fused multiply-add is supported.
-}
data CLDeviceFPConfig = CL_FP_DENORM
                      | CL_FP_INF_NAN
                      | CL_FP_ROUND_TO_NEAREST
                      | CL_FP_ROUND_TO_ZERO
                      | CL_FP_ROUND_TO_INF
                      | CL_FP_FMA
                      deriving (Show,Bounded,Eq,Ord)
instance Enum CLDeviceFPConfig where
  fromEnum CL_FP_DENORM = 1
  fromEnum CL_FP_INF_NAN = 2
  fromEnum CL_FP_ROUND_TO_NEAREST = 4
  fromEnum CL_FP_ROUND_TO_ZERO = 8
  fromEnum CL_FP_ROUND_TO_INF = 16
  fromEnum CL_FP_FMA = 32

  toEnum 1 = CL_FP_DENORM
  toEnum 2 = CL_FP_INF_NAN
  toEnum 4 = CL_FP_ROUND_TO_NEAREST
  toEnum 8 = CL_FP_ROUND_TO_ZERO
  toEnum 16 = CL_FP_ROUND_TO_INF
  toEnum 32 = CL_FP_FMA
  toEnum unmatched = error ("CLDeviceFPConfig.toEnum: Cannot match " ++ show unmatched)

{-# LINE 463 "src/System/GPU/OpenCL/Types.chs" #-}

{-|
 * 'CL_EXEC_KERNEL', The OpenCL device can execute OpenCL kernels.
                            
 * 'CL_EXEC_NATIVE_KERNEL', The OpenCL device can execute native kernels.
-}
data CLDeviceExecCapability = CL_EXEC_KERNEL
                            | CL_EXEC_NATIVE_KERNEL
                            deriving (Show,Bounded,Eq,Ord)
instance Enum CLDeviceExecCapability where
  fromEnum CL_EXEC_KERNEL = 1
  fromEnum CL_EXEC_NATIVE_KERNEL = 2

  toEnum 1 = CL_EXEC_KERNEL
  toEnum 2 = CL_EXEC_NATIVE_KERNEL
  toEnum unmatched = error ("CLDeviceExecCapability.toEnum: Cannot match " ++ show unmatched)

{-# LINE 477 "src/System/GPU/OpenCL/Types.chs" #-}

data CLDeviceMemCacheType = CL_NONE
                          | CL_READ_ONLY_CACHE
                          | CL_READ_WRITE_CACHE
                          deriving (Show)
instance Enum CLDeviceMemCacheType where
  fromEnum CL_NONE = 0
  fromEnum CL_READ_ONLY_CACHE = 1
  fromEnum CL_READ_WRITE_CACHE = 2

  toEnum 0 = CL_NONE
  toEnum 1 = CL_READ_ONLY_CACHE
  toEnum 2 = CL_READ_WRITE_CACHE
  toEnum unmatched = error ("CLDeviceMemCacheType.toEnum: Cannot match " ++ show unmatched)

{-# LINE 486 "src/System/GPU/OpenCL/Types.chs" #-}

data CLDeviceLocalMemType = CL_LOCAL
                          | CL_GLOBAL
                          deriving (Show)
instance Enum CLDeviceLocalMemType where
  fromEnum CL_LOCAL = 1
  fromEnum CL_GLOBAL = 2

  toEnum 1 = CL_LOCAL
  toEnum 2 = CL_GLOBAL
  toEnum unmatched = error ("CLDeviceLocalMemType.toEnum: Cannot match " ++ show unmatched)

{-# LINE 494 "src/System/GPU/OpenCL/Types.chs" #-}

-- -----------------------------------------------------------------------------
-- | Command associated with an event.
data CLCommandType = CL_COMMAND_NDRANGE_KERNEL
                   | CL_COMMAND_TASK
                   | CL_COMMAND_NATIVE_KERNEL
                   | CL_COMMAND_READ_BUFFER
                   | CL_COMMAND_WRITE_BUFFER
                   | CL_COMMAND_COPY_BUFFER
                   | CL_COMMAND_READ_IMAGE
                   | CL_COMMAND_WRITE_IMAGE
                   | CL_COMMAND_COPY_IMAGE
                   | CL_COMMAND_COPY_BUFFER_TO_IMAGE
                   | CL_COMMAND_COPY_IMAGE_TO_BUFFER
                   | CL_COMMAND_MAP_BUFFER
                   | CL_COMMAND_MAP_IMAGE
                   | CL_COMMAND_UNMAP_MEM_OBJECT
                   | CL_COMMAND_MARKER
                   | CL_COMMAND_ACQUIRE_GL_OBJECTS
                   | CL_COMMAND_RELEASE_GL_OBJECTS
                   deriving (Show)
instance Enum CLCommandType where
  fromEnum CL_COMMAND_NDRANGE_KERNEL = 4592
  fromEnum CL_COMMAND_TASK = 4593
  fromEnum CL_COMMAND_NATIVE_KERNEL = 4594
  fromEnum CL_COMMAND_READ_BUFFER = 4595
  fromEnum CL_COMMAND_WRITE_BUFFER = 4596
  fromEnum CL_COMMAND_COPY_BUFFER = 4597
  fromEnum CL_COMMAND_READ_IMAGE = 4598
  fromEnum CL_COMMAND_WRITE_IMAGE = 4599
  fromEnum CL_COMMAND_COPY_IMAGE = 4600
  fromEnum CL_COMMAND_COPY_BUFFER_TO_IMAGE = 4602
  fromEnum CL_COMMAND_COPY_IMAGE_TO_BUFFER = 4601
  fromEnum CL_COMMAND_MAP_BUFFER = 4603
  fromEnum CL_COMMAND_MAP_IMAGE = 4604
  fromEnum CL_COMMAND_UNMAP_MEM_OBJECT = 4605
  fromEnum CL_COMMAND_MARKER = 4606
  fromEnum CL_COMMAND_ACQUIRE_GL_OBJECTS = 4607
  fromEnum CL_COMMAND_RELEASE_GL_OBJECTS = 4608

  toEnum 4592 = CL_COMMAND_NDRANGE_KERNEL
  toEnum 4593 = CL_COMMAND_TASK
  toEnum 4594 = CL_COMMAND_NATIVE_KERNEL
  toEnum 4595 = CL_COMMAND_READ_BUFFER
  toEnum 4596 = CL_COMMAND_WRITE_BUFFER
  toEnum 4597 = CL_COMMAND_COPY_BUFFER
  toEnum 4598 = CL_COMMAND_READ_IMAGE
  toEnum 4599 = CL_COMMAND_WRITE_IMAGE
  toEnum 4600 = CL_COMMAND_COPY_IMAGE
  toEnum 4602 = CL_COMMAND_COPY_BUFFER_TO_IMAGE
  toEnum 4601 = CL_COMMAND_COPY_IMAGE_TO_BUFFER
  toEnum 4603 = CL_COMMAND_MAP_BUFFER
  toEnum 4604 = CL_COMMAND_MAP_IMAGE
  toEnum 4605 = CL_COMMAND_UNMAP_MEM_OBJECT
  toEnum 4606 = CL_COMMAND_MARKER
  toEnum 4607 = CL_COMMAND_ACQUIRE_GL_OBJECTS
  toEnum 4608 = CL_COMMAND_RELEASE_GL_OBJECTS
  toEnum unmatched = error ("CLCommandType.toEnum: Cannot match " ++ show unmatched)

{-# LINE 520 "src/System/GPU/OpenCL/Types.chs" #-}

{-|
 * 'CL_QUEUED', command has been enqueued in the command-queue.

 * 'CL_SUBMITTED', enqueued command has been submitted by the host to the 
device associated with the command-queue.

 * 'CL_RUNNING', device is currently executing this command.
                            
 * 'CL_COMPLETE', the command has completed.
                              
 * 'CL_EXEC_ERROR', command was abnormally terminated.
-}
data CLCommandExecutionStatus = CL_QUEUED
                              | CL_SUBMITTED
                              | CL_RUNNING
                              | CL_COMPLETE
                              | CL_EXEC_ERROR
                              deriving (Show)
instance Enum CLCommandExecutionStatus where
  fromEnum CL_QUEUED = 3
  fromEnum CL_SUBMITTED = 2
  fromEnum CL_RUNNING = 1
  fromEnum CL_COMPLETE = 0
  fromEnum CL_EXEC_ERROR = (-1)

  toEnum 3 = CL_QUEUED
  toEnum 2 = CL_SUBMITTED
  toEnum 1 = CL_RUNNING
  toEnum 0 = CL_COMPLETE
  toEnum (-1) = CL_EXEC_ERROR
  toEnum unmatched = error ("CLCommandExecutionStatus.toEnum: Cannot match " ++ show unmatched)

{-# LINE 541 "src/System/GPU/OpenCL/Types.chs" #-}

{-| Specifies the profiling data.

 * 'CL_PROFILING_COMMAND_QUEUED', A 64-bit value that describes the current 
device time counter in nanoseconds when the command identified by event is 
enqueued in a command-queue by the host.
 
 * 'CL_PROFILING_COMMAND_SUBMIT', A 64-bit value that describes the current 
device time counter in nanoseconds when the command identified by event that has 
been enqueued is submitted by the host to the device associated with the 
commandqueue.
 
 * 'CL_PROFILING_COMMAND_START', A 64-bit value that describes the current 
device time counter in nanoseconds when the command identified by event starts 
execution on the device.
 
 * 'CL_PROFILING_COMMAND_END', A 64-bit value that describes the current device 
time counter in nanoseconds when the command identified by event has finished 
execution on the device.
-}
data CLProfilingInfo = CL_PROFILING_COMMAND_QUEUED
                     | CL_PROFILING_COMMAND_SUBMIT
                     | CL_PROFILING_COMMAND_START
                     | CL_PROFILING_COMMAND_END
                     deriving (Show)
instance Enum CLProfilingInfo where
  fromEnum CL_PROFILING_COMMAND_QUEUED = 4736
  fromEnum CL_PROFILING_COMMAND_SUBMIT = 4737
  fromEnum CL_PROFILING_COMMAND_START = 4738
  fromEnum CL_PROFILING_COMMAND_END = 4739

  toEnum 4736 = CL_PROFILING_COMMAND_QUEUED
  toEnum 4737 = CL_PROFILING_COMMAND_SUBMIT
  toEnum 4738 = CL_PROFILING_COMMAND_START
  toEnum 4739 = CL_PROFILING_COMMAND_END
  toEnum unmatched = error ("CLProfilingInfo.toEnum: Cannot match " ++ show unmatched)

{-# LINE 571 "src/System/GPU/OpenCL/Types.chs" #-}

-- -----------------------------------------------------------------------------
{-| 
 * 'CL_MEM_READ_WRITE', This flag specifies that the memory object will be
read and written by a kernel. This is the default.

 * 'CL_MEM_WRITE_ONLY', This flags specifies that the memory object will be
written but not read by a kernel. Reading from a buffer or image object created
with 'CLMEM_WRITE_ONLY' inside a kernel is undefined.

 * 'CL_MEM_READ_ONLY', This flag specifies that the memory object is a read-only
memory object when used inside a kernel. Writing to a buffer or image object
created with 'CLMEM_READ_ONLY' inside a kernel is undefined.

 * 'CL_MEM_USE_HOST_PTR', This flag is valid only if host_ptr is not NULL. If
specified, it indicates that the application wants the OpenCL implementation to
use memory referenced by host_ptr as the storage bits for the memory
object. OpenCL implementations are allowed to cache the buffer contents pointed
to by host_ptr in device memory. This cached copy can be used when kernels are
executed on a device. The result of OpenCL commands that operate on multiple
buffer objects created with the same host_ptr or overlapping host regions is
considered to be undefined.

 * 'CL_MEM_ALLOC_HOST_PTR', This flag specifies that the application wants the
OpenCL implementation to allocate memory from host accessible
memory. 'CL_MEM_ALLOC_HOST_PTR' and 'CL_MEM_USE_HOST_PTR' are mutually exclusive.

 * 'CL_MEM_COPY_HOST_PTR', This flag is valid only if host_ptr is not NULL. If
specified, it indicates that the application wants the OpenCL implementation to
allocate memory for the memory object and copy the data from memory referenced
by host_ptr. 'CL_MEM_COPY_HOST_PTR' and 'CL_MEM_USE_HOST_PTR' are mutually
exclusive. 'CL_MEM_COPY_HOST_PTR' can be used with 'CL_MEM_ALLOC_HOST_PTR' to
initialize the contents of the cl_mem object allocated using host-accessible
(e.g. PCIe) memory.  
-} 
data CLMemFlag = CL_MEM_READ_WRITE
               | CL_MEM_WRITE_ONLY
               | CL_MEM_READ_ONLY
               | CL_MEM_USE_HOST_PTR
               | CL_MEM_ALLOC_HOST_PTR
               | CL_MEM_COPY_HOST_PTR
               deriving (Show,Bounded,Eq,Ord)
instance Enum CLMemFlag where
  fromEnum CL_MEM_READ_WRITE = 1
  fromEnum CL_MEM_WRITE_ONLY = 2
  fromEnum CL_MEM_READ_ONLY = 4
  fromEnum CL_MEM_USE_HOST_PTR = 8
  fromEnum CL_MEM_ALLOC_HOST_PTR = 16
  fromEnum CL_MEM_COPY_HOST_PTR = 32

  toEnum 1 = CL_MEM_READ_WRITE
  toEnum 2 = CL_MEM_WRITE_ONLY
  toEnum 4 = CL_MEM_READ_ONLY
  toEnum 8 = CL_MEM_USE_HOST_PTR
  toEnum 16 = CL_MEM_ALLOC_HOST_PTR
  toEnum 32 = CL_MEM_COPY_HOST_PTR
  toEnum unmatched = error ("CLMemFlag.toEnum: Cannot match " ++ show unmatched)

{-# LINE 617 "src/System/GPU/OpenCL/Types.chs" #-}

{-| * 'CL_MEM_OBJECT_BUFFER' if memobj is created with 'clCreateBuffer'. 
 
 * 'CL_MEM_OBJECT_IMAGE2D' if memobj is created with 'clCreateImage2D' 

 * 'CL_MEM_OBJECT_IMAGE3D' if memobj is created with 'clCreateImage3D'.
-}
data CLMemObjectType = CL_MEM_OBJECT_BUFFER
                     | CL_MEM_OBJECT_IMAGE2D
                     | CL_MEM_OBJECT_IMAGE3D
                     deriving (Show)
instance Enum CLMemObjectType where
  fromEnum CL_MEM_OBJECT_BUFFER = 4336
  fromEnum CL_MEM_OBJECT_IMAGE2D = 4337
  fromEnum CL_MEM_OBJECT_IMAGE3D = 4338

  toEnum 4336 = CL_MEM_OBJECT_BUFFER
  toEnum 4337 = CL_MEM_OBJECT_IMAGE2D
  toEnum 4338 = CL_MEM_OBJECT_IMAGE3D
  toEnum unmatched = error ("CLMemObjectType.toEnum: Cannot match " ++ show unmatched)

{-# LINE 633 "src/System/GPU/OpenCL/Types.chs" #-}

{-| * 'CL_BUILD_NONE'. The build status returned if no build has been performed
on the specified program object for device.

 * 'CL_BUILD_ERROR'. The build status returned if the last call to
'clBuildProgram' on the specified program object for device generated an error.

 * 'CL_BUILD_SUCCESS'. The build status retrned if the last call to
'clBuildProgram' on the specified program object for device was successful.

 * 'CL_BUILD_IN_PROGRESS'. The build status returned if the last call to 
'clBuildProgram' on the specified program object for device has not finished.
-}
data CLBuildStatus = CL_BUILD_NONE
                   | CL_BUILD_ERROR
                   | CL_BUILD_SUCCESS
                   | CL_BUILD_IN_PROGRESS
                   deriving (Show)
instance Enum CLBuildStatus where
  fromEnum CL_BUILD_NONE = (-1)
  fromEnum CL_BUILD_ERROR = (-2)
  fromEnum CL_BUILD_SUCCESS = 0
  fromEnum CL_BUILD_IN_PROGRESS = (-3)

  toEnum (-1) = CL_BUILD_NONE
  toEnum (-2) = CL_BUILD_ERROR
  toEnum 0 = CL_BUILD_SUCCESS
  toEnum (-3) = CL_BUILD_IN_PROGRESS
  toEnum unmatched = error ("CLBuildStatus.toEnum: Cannot match " ++ show unmatched)

{-# LINE 656 "src/System/GPU/OpenCL/Types.chs" #-}

data CLAddressingMode = CL_ADDRESS_REPEAT
                      | CL_ADDRESS_CLAMP_TO_EDGE
                      | CL_ADDRESS_CLAMP
                      | CL_ADDRESS_NONE
                      deriving (Show)
instance Enum CLAddressingMode where
  fromEnum CL_ADDRESS_REPEAT = 4403
  fromEnum CL_ADDRESS_CLAMP_TO_EDGE = 4401
  fromEnum CL_ADDRESS_CLAMP = 4402
  fromEnum CL_ADDRESS_NONE = 4400

  toEnum 4403 = CL_ADDRESS_REPEAT
  toEnum 4401 = CL_ADDRESS_CLAMP_TO_EDGE
  toEnum 4402 = CL_ADDRESS_CLAMP
  toEnum 4400 = CL_ADDRESS_NONE
  toEnum unmatched = error ("CLAddressingMode.toEnum: Cannot match " ++ show unmatched)

{-# LINE 666 "src/System/GPU/OpenCL/Types.chs" #-}

data CLFilterMode = CL_FILTER_NEAREST
                  | CL_FILTER_LINEAR
                  deriving (Show)
instance Enum CLFilterMode where
  fromEnum CL_FILTER_NEAREST = 4416
  fromEnum CL_FILTER_LINEAR = 4417

  toEnum 4416 = CL_FILTER_NEAREST
  toEnum 4417 = CL_FILTER_LINEAR
  toEnum unmatched = error ("CLFilterMode.toEnum: Cannot match " ++ show unmatched)

{-# LINE 674 "src/System/GPU/OpenCL/Types.chs" #-}

-- -----------------------------------------------------------------------------
getCLValue :: (Enum a, Integral b) => a -> b
getCLValue = fromIntegral . fromEnum

getEnumCL :: (Integral a, Enum b) => a -> b
getEnumCL = toEnum . fromIntegral 

getCommandExecutionStatus :: CLint -> CLCommandExecutionStatus
getCommandExecutionStatus n 
  | n < 0 = CL_EXEC_ERROR
  | otherwise = getEnumCL $ n
                
-- -----------------------------------------------------------------------------
binaryFlags :: (Ord b, Enum b, Bounded b) => b -> [b]
binaryFlags m = map toEnum . takeWhile (<= (fromEnum m)) $ [1 `shiftL` n | n <- [0..]]
  
testMask :: Bits b => b -> b -> Bool
testMask mask v = (v .&. mask) == v

bitmaskFromFlags :: (Enum a, Bits b) => [a] -> b
bitmaskFromFlags = foldl' (.|.) 0 . map (fromIntegral . fromEnum)

bitmaskToFlags :: (Enum a, Bits b) => [a] -> b -> [a]
bitmaskToFlags xs mask = filter (testMask mask . fromIntegral . fromEnum) xs

bitmaskToDeviceTypes :: CLDeviceType_ -> [CLDeviceType]
bitmaskToDeviceTypes = bitmaskToFlags [CL_DEVICE_TYPE_CPU,CL_DEVICE_TYPE_GPU,CL_DEVICE_TYPE_ACCELERATOR,CL_DEVICE_TYPE_DEFAULT,CL_DEVICE_TYPE_ALL]

bitmaskToCommandQueueProperties :: CLCommandQueueProperty_ -> [CLCommandQueueProperty]
bitmaskToCommandQueueProperties = bitmaskToFlags (binaryFlags maxBound)
      
bitmaskToFPConfig :: CLDeviceFPConfig_ -> [CLDeviceFPConfig]
bitmaskToFPConfig = bitmaskToFlags (binaryFlags maxBound)

bitmaskToExecCapability :: CLDeviceExecCapability_ -> [CLDeviceExecCapability]
bitmaskToExecCapability = bitmaskToFlags (binaryFlags maxBound)

bitmaskToMemFlags :: CLMemFlags_ -> [CLMemFlag]
bitmaskToMemFlags = bitmaskToFlags (binaryFlags maxBound)

-- -----------------------------------------------------------------------------