module Graphics.GD ( -- * Types Image, Size, Point, Color, -- * Creating and copying images newImage, copyImage, -- * Loading images -- ** JPEG loadJpegFile, loadJpegData, -- ** PNG loadPngFile, loadPngData, -- ** GIF loadGifFile, loadGifData, -- * Saving images -- ** JPEG saveJpegFile, -- ** PNG savePngFile, -- ** GIF saveGifFile, -- * Getting image information imageSize, -- * Manipulating images resizeImage, rotateImage, -- * Drawing fillImage, drawFilledRectangle, drawFilledEllipse, antiAliased, -- * Colors rgb, rgba ) where import Control.Exception (bracket) import Control.Monad (liftM) import Foreign import Foreign.C import Foreign.ForeignPtr import Foreign.Marshal.Error data CFILE = CFILE foreign import ccall "stdio.h fopen" c_fopen :: CString -> CString -> IO (Ptr CFILE) foreign import ccall "stdio.h fclose" c_fclose :: Ptr CFILE -> IO CInt fopen :: FilePath -> String -> IO (Ptr CFILE) fopen file mode = throwErrnoIfNull file $ withCString file $ \f -> withCString mode $ \m -> c_fopen f m fclose :: Ptr CFILE -> IO () fclose p = throwErrnoIf_ (== #{const EOF}) "fclose" $ c_fclose p withCFILE :: FilePath -> String -> (Ptr CFILE -> IO a) -> IO a withCFILE file mode = bracket (fopen file mode) fclose #include #include "gd-extras.h" data GDImage = GDImage -- JPEG format foreign import ccall "gd.h gdImageCreateFromJpeg" gdImageCreateFromJpeg :: Ptr CFILE -> IO (Ptr GDImage) foreign import ccall "gd.h gdImageCreateFromJpegPtr" gdImageCreateFromJpegPtr :: CInt -> Ptr a -> IO (Ptr GDImage) foreign import ccall "gd.h gdImageJpeg" gdImageJpeg :: Ptr GDImage -> Ptr CFILE -> CInt -> IO () -- PNG format foreign import ccall "gd.h gdImageCreateFromPng" gdImageCreateFromPng :: Ptr CFILE -> IO (Ptr GDImage) foreign import ccall "gd.h gdImageCreateFromPngPtr" gdImageCreateFromPngPtr :: CInt -> Ptr a -> IO (Ptr GDImage) foreign import ccall "gd.h gdImagePng" gdImagePng :: Ptr GDImage -> Ptr CFILE -> IO () -- GIF format foreign import ccall "gd.h gdImageCreateFromGif" gdImageCreateFromGif :: Ptr CFILE -> IO (Ptr GDImage) foreign import ccall "gd.h gdImageCreateFromGifPtr" gdImageCreateFromGifPtr :: CInt -> Ptr a -> IO (Ptr GDImage) foreign import ccall "gd.h gdImageGif" gdImageGif :: Ptr GDImage -> Ptr CFILE -> IO () -- Creating and destroying images foreign import ccall "gd.h gdImageCreateTrueColor" gdImageCreateTrueColor :: CInt -> CInt -> IO (Ptr GDImage) foreign import ccall "gd.h &gdImageDestroy" ptr_gdImageDestroy :: FunPtr (Ptr GDImage -> IO ()) -- Copying image parts foreign import ccall "gd.h gdImageCopy" gdImageCopy :: Ptr GDImage -> Ptr GDImage -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> IO () foreign import ccall "gd.h gdImageCopyResampled" gdImageCopyResampled :: Ptr GDImage -> Ptr GDImage -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> IO () {- foreign import ccall "gd.h gdImageCopyRotated" gdImageCopyRotated :: Ptr GDImage -> Ptr GDImage -> CDouble -> CDouble -> CInt -> CInt -> CInt -> CInt -> CInt -> IO () -} foreign import ccall "gd-extras.h gdImageCopyRotated90" gdImageCopyRotated90 :: Ptr GDImage -> Ptr GDImage -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> IO () -- Drawing functions foreign import ccall "gd.h gdImageFilledRectangle" gdImageFilledRectangle :: Ptr GDImage -> CInt -> CInt -> CInt -> CInt -> CInt -> IO () foreign import ccall "gd.h gdImageFilledEllipse" gdImageFilledEllipse :: Ptr GDImage -> CInt -> CInt -> CInt -> CInt -> CInt -> IO () foreign import ccall "gd.h gdImageSetAntiAliased" gdImageSetAntiAliased :: Ptr GDImage -> CInt -> IO () type Image = ForeignPtr GDImage type Size = (Int,Int) type Point = (Int,Int) type Color = CInt -- | Call gd_free_image when the image is garbage collected. mkImage :: Ptr GDImage -> IO Image mkImage p = newForeignPtr ptr_gdImageDestroy p withImage :: Image -> (Ptr GDImage -> IO a) -> IO a withImage = withForeignPtr -- | Create a new empty image. newImage :: Size -> IO Image newImage (w,h) = newImage_ (int w) (int h) newImage_ :: CInt -> CInt -> IO Image newImage_ w h = do p <- throwIfNull "gdImageCreateTrueColor" $ gdImageCreateTrueColor w h mkImage p -- | Create a new empty image and apply a function to it. onNewImage :: CInt -> CInt -> (Ptr GDImage -> IO a) -> IO Image onNewImage w h f = newImage_ w h >>= \i -> withImage i f >> return i -- | Make a copy of an image. copyImage :: Image -> IO Image copyImage i = withImage i f where f p = do (w,h) <- imageSize_ p onNewImage w h (\p' -> gdImageCopy p' p 0 0 0 0 w h) -- -- * Loading images -- -- | Load a JPEG image from a file. loadJpegFile :: FilePath -> IO Image loadJpegFile = loadImageFile gdImageCreateFromJpeg -- | Load a JPEG image from a buffer. loadJpegData :: Int -- ^ Buffer size. -> Ptr a -- ^ Buffer with image data. -> IO Image loadJpegData = loadImageData gdImageCreateFromJpegPtr -- | Load a PNG image from a file. loadPngFile :: FilePath -> IO Image loadPngFile = loadImageFile gdImageCreateFromPng -- | Load a PNG image from a buffer. loadPngData :: Int -- ^ Buffer size. -> Ptr a -- ^ Buffer with image data. -> IO Image loadPngData = loadImageData gdImageCreateFromPngPtr -- | Load a GIF image from a file. loadGifFile :: FilePath -> IO Image loadGifFile = loadImageFile gdImageCreateFromGif -- | Load a GIF image from a buffer. loadGifData :: Int -- ^ Buffer size. -> Ptr a -- ^ Buffer with image data. -> IO Image loadGifData = loadImageData gdImageCreateFromGifPtr loadImageFile :: (Ptr CFILE -> IO (Ptr GDImage)) -> FilePath -> IO Image loadImageFile f file = do p <- throwIfNull ("Loading image from " ++ file) $ withCFILE file "rb" f mkImage p loadImageData :: (CInt -> Ptr a -> IO (Ptr GDImage)) -> Int -> Ptr a -> IO Image loadImageData f sz buf = do p <- throwIfNull ("Loading image") $ f (fromIntegral sz) buf mkImage p -- -- * Saving images -- -- | Save an image as a JPEG file. saveJpegFile :: Int -- ^ quality: 0-95, or negative for default quality. -> FilePath -> Image -> IO () saveJpegFile q = saveImageFile (\p h -> gdImageJpeg p h (fromIntegral q)) -- | Save an image as a PNG file. savePngFile :: FilePath -> Image -> IO () savePngFile = saveImageFile gdImagePng -- | Save an image as a GIF file. saveGifFile :: FilePath -> Image -> IO () saveGifFile = saveImageFile gdImageGif saveImageFile :: (Ptr GDImage -> Ptr CFILE -> IO ()) -> FilePath -> Image -> IO () saveImageFile f file i = withImage i (\p -> withCFILE file "wb" (f p)) -- -- * Getting information about images. -- -- | Get the size of an image. imageSize :: Image -> IO (Int,Int) -- ^ (width, height) imageSize i = liftM f $ withImage i imageSize_ where f = (\ (w,h) -> (fromIntegral w, fromIntegral h)) imageSize_ :: Ptr GDImage -> IO (CInt,CInt) imageSize_ p = do w <- #{peek gdImage, sx} p h <- #{peek gdImage, sy} p return (w, h) -- -- * Transforming images. -- -- | Resize an image to a give size. resizeImage :: Int -- ^ width in pixels of output image -> Int -- ^ height in pixels of output image -> Image -> IO Image resizeImage w h i = withImage i f where f p = do let (outW,outH) = (fromIntegral w, fromIntegral h) (inW, inH) <- imageSize_ p onNewImage outW outH $ \p' -> gdImageCopyResampled p' p 0 0 0 0 outW outH inW inH -- | Rotate an image by a multiple of 90 degrees counter-clockwise. rotateImage :: Int -- ^ 1 for 90 degrees counter-clockwise, -- 2 for 180 degrees, etc. -> Image -> IO Image rotateImage r i = withImage i f where f p = do (inW,inH) <- imageSize_ p let q = fromIntegral (r `mod` 4) (outW,outH) | r `mod` 2 == 0 = (inW,inH) | otherwise = (inH,inW) srcX = if q == 1 || q == 2 then inW-1 else 0; srcY = if q == 2 || q == 3 then inH-1 else 0; onNewImage outW outH (\p' -> gdImageCopyRotated90 p' p 0 0 srcX srcY inW inH q) -- -- * Drawing -- -- | Fill the entire image with the given color. fillImage :: Color -> Image -> IO () fillImage c i = do sz <- imageSize i drawFilledRectangle (0,0) sz c i drawFilledRectangle :: Point -- ^ Upper left corner -> Point -- ^ Lower right corner -> Color -> Image -> IO () drawFilledRectangle (x1,y1) (x2,y2) c i = withImage i $ \p -> gdImageFilledRectangle p (int x1) (int y1) (int x2) (int y2) c drawFilledEllipse :: Point -- ^ Center -> Size -- ^ Width and height -> Color -> Image -> IO () drawFilledEllipse (cx,cy) (w,h) c i = withImage i $ \p -> gdImageFilledEllipse p (int cx) (int cy) (int w) (int h) c -- | Use anti-aliasing when performing the given drawing function. -- This can cause a segault with some gd versions. antiAliased :: (Color -> Image -> IO a) -> Color -> Image -> IO a antiAliased f c i = do withImage i (\p -> gdImageSetAntiAliased p c) f (#{const gdAntiAliased}) i -- -- * Colors -- rgb :: Int -- ^ Red (0-255) -> Int -- ^ Green (0-255) -> Int -- ^ Blue (0-255) -> Color rgb r g b = rgba r g b 0 rgba :: Int -- ^ Red (0-255) -> Int -- ^ Green (0-255) -> Int -- ^ Blue (0-255) -> Int -- ^ Alpha (0-127), 0 is opaque, 127 is transparent -> Color rgba r g b a = (int a `shiftL` 24) .|. (int r `shiftL` 16) .|. (int g `shiftL` 8) .|. int b -- -- * Utilities -- int :: (Integral a, Num b) => a -> b int = fromIntegral