module Graphics.Gloss.Juicy
    (
    
      fromDynamicImage
    , fromImageRGBA8
    , fromImageRGB8
    , fromImageY8
    , fromImageYA8
    , fromImageYCbCr8
    
    , loadJuicy
    , loadJuicyJPG
    , loadJuicyPNG
    
    , loadBMP
    )
where
import Codec.Picture
import Codec.Picture.Types
import Graphics.Gloss.Data.Picture
import Graphics.Gloss.Data.Bitmap
import Data.Vector.Storable        (unsafeToForeignPtr)
fromDynamicImage :: DynamicImage -> Maybe Picture
fromDynamicImage (ImageY8 img)     = Just $ fromImageY8 img
fromDynamicImage (ImageYA8 img)    = Just $ fromImageYA8 img
fromDynamicImage (ImageRGB8 img)   = Just $ fromImageRGB8 img
fromDynamicImage (ImageRGBA8 img)  = Just $ fromImageRGBA8 img
fromDynamicImage (ImageYCbCr8 img) = Just $ fromImageYCbCr8 img
fromDynamicImage (ImageRGBF _)     = Nothing
fromDynamicImage (ImageYF _)       = Nothing
fromImageRGBA8 :: Image PixelRGBA8 -> Picture
fromImageRGBA8 (Image { imageWidth = w, imageHeight = h, imageData = id }) =
  bitmapOfForeignPtr w h
                     (BitmapFormat TopToBottom PxRGBA)
                     ptr True
    where (ptr, _, _) = unsafeToForeignPtr id
fromImageRGB8 :: Image PixelRGB8 -> Picture
fromImageRGB8 = fromImageRGBA8 . promoteImage
fromImageY8 :: Image Pixel8 -> Picture
fromImageY8 = fromImageRGBA8 . promoteImage
fromImageYA8 :: Image PixelYA8 -> Picture
fromImageYA8 = fromImageRGBA8 . promoteImage
fromImageYCbCr8 :: Image PixelYCbCr8 -> Picture
fromImageYCbCr8 = fromImageRGB8 . convertImage
loadJuicy :: FilePath -> IO (Maybe Picture)
loadJuicy = loadWith readImage
loadJuicyJPG :: FilePath -> IO (Maybe Picture)
loadJuicyJPG = loadWith readJpeg
loadJuicyPNG :: FilePath -> IO (Maybe Picture)
loadJuicyPNG = loadWith readPng
loadWith :: (FilePath -> IO (Either String DynamicImage)) -> FilePath -> IO (Maybe Picture)
loadWith reader fp = do
    eImg <- reader fp
    return $ either (const Nothing) fromDynamicImage eImg