module Codec.Image.STB
( Bitmap
, Image
, decodeImage
, decodeImage'
, loadImage
, loadImage'
) where
import Data.Bitmap.Pure
import Control.Monad (liftM)
import Control.Exception
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import Foreign
import Foreign.C
import System.IO
import System.IO.Error
#if (__GLASGOW_HASKELL__ == 606)
import Data.ByteString.Base
#else
import Data.ByteString.Internal
#endif
type Image = Bitmap Word8
foreign import ccall safe "stb_image.h stbi_load_from_memory"
stbi_load_from_memory :: Ptr Word8 -> CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> CInt -> IO (Ptr Word8)
foreign import ccall safe "stb_image.h &stbi_image_free"
stbi_image_free :: FunPtr (Ptr a -> IO ())
foreign import ccall safe "stb_image.h stbi_failure_reason"
stbi_failure_reason :: IO (Ptr CChar)
decodeImage :: ByteString -> IO (Either String Image)
decodeImage = decodeImage' 0
decodeImage' :: Int -> ByteString -> IO (Either String Image)
decodeImage' forcecomp bs = do
let (fptr,ofs,len) = toForeignPtr bs
withForeignPtr fptr $ \q -> do
let ptr = plusPtr q ofs
alloca $ \pxres -> alloca $ \pyres -> alloca $ \pcomp -> do
r <- stbi_load_from_memory ptr (fromIntegral len) pxres pyres pcomp (fromIntegral forcecomp)
if r == nullPtr
then do
e <- stbi_failure_reason
msg <- peekCString e
return $ Left msg
else do
fr <- newForeignPtr stbi_image_free r
xres <- liftM fromIntegral $ peek pxres
yres <- liftM fromIntegral $ peek pyres
comp <- liftM fromIntegral $ peek pcomp
let bm = bitmapFromForeignPtrUnsafe (xres,yres) comp 1 0 fr
return (Right bm)
#if (BASE_MAJOR_VERSION >= 4)
ioHandler :: IOException -> IO (Either String a)
ioHandler ioerror = return $ Left $ "IO error: " ++ ioeGetErrorString ioerror
#else
ioHandler :: Exception -> IO (Either String a)
ioHandler (IOException ioerror) = return $ Left $ "IO error: " ++ ioeGetErrorString ioerror
ioHandler _ = return $ Left "Unknown error"
#endif
loadImage :: FilePath -> IO (Either String Image)
loadImage path = handle ioHandler $ do
h <- openBinaryFile path ReadMode
b <- B.hGetContents h
hClose h
decodeImage b
loadImage':: FilePath -> Int -> IO (Either String Image)
loadImage' path ncomps = handle ioHandler $ do
h <- openBinaryFile path ReadMode
b <- B.hGetContents h
hClose h
decodeImage' ncomps b