{-# LANGUAGE ForeignFunctionInterface #-} {- | Module : Graphics.V4L2.IOCtl Maintainer : claude@mathr.co.uk Stability : no Portability : no Heavily based on the 'ioctl' package (c) Maciej Piechotka. -} module Graphics.V4L2.IOCtl ( ioctl , ioctl_ , ioctl' , zero ) where import Foreign (Ptr, Storable, alloca, castPtr, peek, sizeOf, with) import Foreign.C (CInt(..), CSize(..), throwErrnoIfMinus1_) import System.Posix.IOCtl (IOControl(ioctlReq)) import System.IO.Unsafe (unsafePerformIO) import Bindings.LibV4L2 (c'v4l2_ioctl) import Graphics.V4L2.Device (Device) c_ioctl' :: IOControl req d => Device -> req -> Ptr d -> IO () c_ioctl' f req p = throwErrnoIfMinus1_ "ioctl" $ c'v4l2_ioctl (fromIntegral f) (fromIntegral $ ioctlReq req) (castPtr p) -- | Calls a ioctl reading the structure after the call ioctl :: IOControl req d => Device -- ^ The file descriptor -> req -- ^ The request -> d -- ^ The data -> IO d -- ^ The data after the call ioctl f req d = with d $ \p -> c_ioctl' f req p >> peek p -- | Call a ioctl ignoring the result ioctl_ :: IOControl req d => Device -- ^ The file descriptor -> req -- ^ The request -> d -- ^ The data -> IO () ioctl_ f req d = with d $ \p -> c_ioctl' f req p -- | Call a ioctl with uninitialized data ioctl' :: IOControl req d => Device -- ^ The file descriptor -> req -- ^ The request -> IO d -- ^ The data ioctl' f req = alloca $ \p -> c_ioctl' f req p >> peek p {- | A value obtained by peeking cleared memory. -} zero :: Storable a => IO a zero = alloca $ \p -> c'memset p 0 (fromIntegral $ sizeOf (undefined `asTypeOf` unsafePerformIO (peek p))) >> peek p foreign import ccall "string.h memset" c'memset :: Ptr a -> CInt -> CSize -> IO (Ptr a)