{-# LINE 1 "Bindings/LibV4L2.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LINE 2 "Bindings/LibV4L2.hsc" #-}

{-# LINE 3 "Bindings/LibV4L2.hsc" #-}

{-# LINE 4 "Bindings/LibV4L2.hsc" #-}
-- | Bindings for libv4l2 on Linux, wrapping:
--   <file:///usr/include/libv4l2.h>
module Bindings.LibV4L2 where
import Foreign.Ptr (Ptr,FunPtr,plusPtr)
import Foreign.Ptr (wordPtrToPtr,castPtrToFunPtr)
import Foreign.Storable
import Foreign.C.Types
import Foreign.C.String (CString,CStringLen,CWString,CWStringLen)
import Foreign.Marshal.Alloc (alloca)
import Foreign.Marshal.Array (peekArray,pokeArray)
import Data.Int
import Data.Word

{-# LINE 8 "Bindings/LibV4L2.hsc" #-}
foreign import ccall "v4l2_open" c'v4l2_open
  :: Ptr CChar -> CInt -> CInt -> IO CInt
foreign import ccall "&v4l2_open" p'v4l2_open
  :: FunPtr (Ptr CChar -> CInt -> CInt -> IO CInt)

{-# LINE 9 "Bindings/LibV4L2.hsc" #-}
foreign import ccall "v4l2_close" c'v4l2_close
  :: CInt -> IO CInt
foreign import ccall "&v4l2_close" p'v4l2_close
  :: FunPtr (CInt -> IO CInt)

{-# LINE 10 "Bindings/LibV4L2.hsc" #-}
foreign import ccall "v4l2_dup" c'v4l2_dup
  :: CInt -> IO CInt
foreign import ccall "&v4l2_dup" p'v4l2_dup
  :: FunPtr (CInt -> IO CInt)

{-# LINE 11 "Bindings/LibV4L2.hsc" #-}
foreign import ccall "v4l2_ioctl" c'v4l2_ioctl
  :: CInt -> CULong -> Ptr a -> IO CInt
foreign import ccall "&v4l2_ioctl" p'v4l2_ioctl
  :: FunPtr (CInt -> CULong -> Ptr a -> IO CInt)

{-# LINE 12 "Bindings/LibV4L2.hsc" #-}
foreign import ccall "v4l2_read" c'v4l2_read
  :: CInt -> Ptr a -> CSize -> IO CInt
foreign import ccall "&v4l2_read" p'v4l2_read
  :: FunPtr (CInt -> Ptr a -> CSize -> IO CInt)

{-# LINE 13 "Bindings/LibV4L2.hsc" #-}
foreign import ccall "v4l2_mmap" c'v4l2_mmap
  :: Ptr a -> CSize -> CInt -> CInt -> CInt -> Int64 -> IO (Ptr a)
foreign import ccall "&v4l2_mmap" p'v4l2_mmap
  :: FunPtr (Ptr a -> CSize -> CInt -> CInt -> CInt -> Int64 -> IO (Ptr a))

{-# LINE 14 "Bindings/LibV4L2.hsc" #-}
foreign import ccall "v4l2_munmap" c'v4l2_munmap
  :: Ptr a -> CSize -> IO CInt
foreign import ccall "&v4l2_munmap" p'v4l2_munmap
  :: FunPtr (Ptr a -> CSize -> IO CInt)

{-# LINE 15 "Bindings/LibV4L2.hsc" #-}
foreign import ccall "v4l2_set_control" c'v4l2_set_control
  :: CInt -> CInt -> CInt -> IO CInt
foreign import ccall "&v4l2_set_control" p'v4l2_set_control
  :: FunPtr (CInt -> CInt -> CInt -> IO CInt)

{-# LINE 16 "Bindings/LibV4L2.hsc" #-}
foreign import ccall "v4l2_get_control" c'v4l2_get_control
  :: CInt -> CInt -> IO CInt
foreign import ccall "&v4l2_get_control" p'v4l2_get_control
  :: FunPtr (CInt -> CInt -> IO CInt)

{-# LINE 17 "Bindings/LibV4L2.hsc" #-}
foreign import ccall "v4l2_fd_open" c'v4l2_fd_open
  :: CInt -> CInt -> IO CInt
foreign import ccall "&v4l2_fd_open" p'v4l2_fd_open
  :: FunPtr (CInt -> CInt -> IO CInt)

{-# LINE 18 "Bindings/LibV4L2.hsc" #-}
c'V4L2_DISABLE_CONVERSION = 1
c'V4L2_DISABLE_CONVERSION :: (Num a) => a

{-# LINE 19 "Bindings/LibV4L2.hsc" #-}
c'V4L2_ENABLE_ENUM_FMT_EMULATION = 2
c'V4L2_ENABLE_ENUM_FMT_EMULATION :: (Num a) => a

{-# LINE 20 "Bindings/LibV4L2.hsc" #-}