{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
{- |
Module      : Graphics.V4L2.Device
Maintainer  : claude@mathr.co.uk
Stability   : no
Portability : no
-}
module Graphics.V4L2.Device
  ( Device()
  , openDevice
  , closeDevice
  , withDevice
  ) where

import Control.Exception (bracket)
import Data.Bits (Bits)
import Data.Typeable (Typeable)
import Foreign.C.Error (throwErrnoIfMinus1, throwErrnoIfMinus1_)
import Foreign.C.String (withCString)
import Foreign.Storable (Storable)
import System.Posix.Types (Fd)

import Bindings.LibV4L2 (c'v4l2_open, c'v4l2_close)
import Bindings.Posix.Fcntl (c'O_RDWR)

{- |  Device handle. -}
newtype Device = Device Fd
  deriving (Bits, Bounded, Enum, Eq, Integral, Num, Ord, Read, Real, Show, Storable, Typeable)

{- |  Open a device.
      Fails with invalid argument when the device is not a V4L2 device.
-}
openDevice :: FilePath {- ^ device name -} -> IO Device
openDevice f = withCString f $ \s -> do
  h <- throwErrnoIfMinus1 "Graphics.V4L2.Device.openDevice" (c'v4l2_open s c'O_RDWR 0)
  return (fromIntegral h)

{- |  Close a device. -}
closeDevice :: Device {- ^ device handle -} -> IO ()
closeDevice d = throwErrnoIfMinus1_ "Graphics.V4L2.Device.closeDevice" (c'v4l2_close (fromIntegral d))

{- |  Perform an action with a device.
      The device will be close on exit from withDevice, whether by
      normal termination or by raising an exception.  If closing the
      device raises an exception, then this exception will be raised by
      'withDevice' rather than any exception raised by the action.
-}
withDevice :: FilePath {- ^ device name -} -> (Device -> IO a) {- ^ action -} -> IO a
withDevice f = bracket (openDevice f) closeDevice