Skip to content

Commit

Permalink
Add getImage and getPixel
Browse files Browse the repository at this point in the history
  • Loading branch information
Dan Rosén committed Nov 4, 2014
1 parent 222091e commit f9054bd
Showing 1 changed file with 22 additions and 5 deletions.
27 changes: 22 additions & 5 deletions Graphics/X11/Xlib/Image.hs
Expand Up @@ -17,6 +17,9 @@ module Graphics.X11.Xlib.Image(
createImage,
putImage,
destroyImage,
getImage,
xGetPixel,
getPixel
) where

import Graphics.X11.Types
Expand All @@ -26,6 +29,8 @@ import Foreign
-- import Foreign.C
import Foreign.C.Types

import System.IO.Unsafe

----------------------------------------------------------------
-- Image
----------------------------------------------------------------
Expand All @@ -36,7 +41,7 @@ createImage display vis depth format offset dat width height bitmap_pad bytes_pe
image <- throwIfNull "createImage" (xCreateImage display vis depth format offset dat width height bitmap_pad bytes_per_line)
return (Image image)
foreign import ccall unsafe "HsXlib.h XCreateImage"
xCreateImage :: Display -> Visual -> CInt -> ImageFormat -> CInt ->
xCreateImage :: Display -> Visual -> CInt -> ImageFormat -> CInt ->
Ptr CChar -> Dimension -> Dimension -> CInt -> CInt -> IO (Ptr Image)

-- | interface to the X11 library function @XPutImage()@.
Expand All @@ -48,13 +53,25 @@ foreign import ccall unsafe "HsXlib.h XPutImage"
foreign import ccall unsafe "HsXlib.h XDestroyImage"
destroyImage :: Image -> IO ()

-- | interface to the X11 library function @XGetImage()@.
getImage :: Display -> Drawable -> CInt -> CInt -> CUInt -> CUInt -> CULong -> ImageFormat -> IO Image
getImage display d x y width height plane_mask format = do
image <- throwIfNull "getImage" (xGetImage display d x y width height plane_mask format)
return (Image image)

foreign import ccall unsafe "HsXlib.h XGetImage"
xGetImage :: Display -> Drawable -> CInt -> CInt -> CUInt -> CUInt -> CULong -> ImageFormat -> IO (Ptr Image)

foreign import ccall unsafe "HsXlib.h XGetPixel"
xGetPixel :: Image -> CInt -> CInt -> IO CULong

-- | interface to the X11 library function @XGetPixel()@.
getPixel :: Image -> CInt -> CInt -> CULong
getPixel i x y = unsafePerformIO (xGetPixel i x y)

{- don't need XInitImage since Haskell users probably won't be setting
members of the XImage structure themselves -}
-- XInitImage omitted

{- these two functions are for fetching image data from a drawable
back into an image struct. i'm not exactly sure when they would be
used -}
-- XGetImage omitted
-- XGetSubImage omitted

0 comments on commit f9054bd

Please sign in to comment.