repa-v4l2-0.2.0.0: Provides high-level access to webcams.

Safe HaskellNone

Graphics.Webcam.Linux

Contents

Description

The Linux interface for accessing webcams via video4linux. This module uses the lower-level bindings to v4l to provide for a simple way to access a web camera from Haskell code using repa. The module is meant to be used like shown in the file example.hs in the root of the package. For example:

 main = runCam (Webcam 0) $ 
                grab >>= saveBmp "1.bmp" >> 
                grab >>= saveBmp "2.bmp" >> 
                grab >>= saveBmp "3.bmp"

This example would take three pictures from the first webcam and store them in three files.

Synopsis

Data Types

data Webcam Source

Constructors

Webcam Int 

type Image r a = Array r DIM3 aSource

An image data type. This uses the Array type Data.Array.Repa.Array.

data V4lCamT m a Source

Instances

MonadTrans V4lCamT 
Monad m => MonadError String (V4lCamT m) 
Monad m => Monad (V4lCamT m) 
Monad m => Functor (V4lCamT m) 
Monad m => MonadPlus (V4lCamT m) 
MonadIO m => MonadIO (V4lCamT m) 

liftIO :: MonadIO m => forall a. IO a -> m a

Lift a computation from the IO monad.

Camera Actions

runCam :: MonadIO m => Webcam -> V4lCamT m a -> m (Either String a)Source

Given a Webcam, runs a V4lCamT action with it. All actions may throwError, which can be caught with catchError. In case of an error, runCam returns Left with an errormessage. Otherwise, it returns a Right with the result.

This function sets a reasonable image format using findImageFormat after opening the webcam. Then, the supplied action is run and the camera is closed again.

You may want to set a different image size or image format, when that is supported.

runCamWith :: MonadIO m => CamState -> V4lCamT m a -> m (Either String a)Source

Like runCam, but runs with a given state.

grab :: MonadIO m => V4lCamT m (Image U Word8)Source

Grab a new image from the currently open camera. May throwError if something goes wrong.

grabF :: MonadIO m => (Image D Word8 -> Image D Word8) -> V4lCamT m (Image F Word8)Source

Like grab, but applies the given function to the captured image.

setSize :: MonadIO m => (Int, Int) -> V4lCamT m ()Source

This function sets the size to the next fitting size the connected web camera supports. You can query the actual size with getSize.

getSize :: Monad m => V4lCamT m (Int, Int)Source

Returns the image with and height of the images captured by the currently open web cam.

getState :: Monad m => V4lCamT m CamStateSource

Get the state data. Internal.

saveBmp :: (MonadIO m, Source r Word8) => FilePath -> Image r Word8 -> V4lCamT m ()Source

Save the given Image as BMP in the file with the given name. This function currently takes a detour via lists when converting the image to a ByteString, and is therefore probably slower than necessary (FIXME).

getImageFormat :: Monad m => V4lCamT m ImageFormatSource

Get the currently used image format. May throwError if the format has not been set.

findImageFormat :: MonadIO m => V4lCamT m ()Source

Finds an image format, sets the current device to it and sets it so it can be retrieved with getImageFormat. Currently this function will set a PixelRGB24 format. Add more intelligence to this if needed.

Utility Functions

rgbaToAbgr :: Source r a => Image r a -> Image D aSource

flipY :: Source r a => Image r a -> Image D aSource

Flips the Y axis of a given image.