X11-1.9.2: A binding to the X11 graphics library

Copyright(c) Frederik Eaton 2006
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org, frederik@ofb.net
Stabilityprovisional
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Graphics.X11.Xlib.Image

Description

Xlib image routines

Synopsis

Documentation

data Image Source #

pointer to an X11 XImage structure

Instances
Eq Image Source # 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

(==) :: Image -> Image -> Bool #

(/=) :: Image -> Image -> Bool #

Data Image Source # 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Image -> c Image #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Image #

toConstr :: Image -> Constr #

dataTypeOf :: Image -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Image) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Image) #

gmapT :: (forall b. Data b => b -> b) -> Image -> Image #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r #

gmapQ :: (forall d. Data d => d -> u) -> Image -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Image -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Image -> m Image #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Image -> m Image #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Image -> m Image #

Ord Image Source # 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

compare :: Image -> Image -> Ordering #

(<) :: Image -> Image -> Bool #

(<=) :: Image -> Image -> Bool #

(>) :: Image -> Image -> Bool #

(>=) :: Image -> Image -> Bool #

max :: Image -> Image -> Image #

min :: Image -> Image -> Image #

Show Image Source # 
Instance details

Defined in Graphics.X11.Xlib.Types

Methods

showsPrec :: Int -> Image -> ShowS #

show :: Image -> String #

showList :: [Image] -> ShowS #

createImage :: Display -> Visual -> CInt -> ImageFormat -> CInt -> Ptr CChar -> Dimension -> Dimension -> CInt -> CInt -> IO Image Source #

interface to the X11 library function XCreateImage().

putImage :: Display -> Drawable -> GC -> Image -> Position -> Position -> Position -> Position -> Dimension -> Dimension -> IO () Source #

interface to the X11 library function XPutImage().

destroyImage :: Image -> IO () Source #

interface to the X11 library function XDestroyImage().

getImage :: Display -> Drawable -> CInt -> CInt -> CUInt -> CUInt -> CULong -> ImageFormat -> IO Image Source #

interface to the X11 library function XGetImage().

getPixel :: Image -> CInt -> CInt -> CULong Source #

interface to the X11 library function XGetPixel().