module Graphics.Gloss.Export.Image
( Size
, Animation
, initialize
, pictureToImageRGB8
, pictureToImageRGBA8
, exportPictureToFormat
, exportPicturesToFormat
) where
import Codec.Picture.Types (Image(..), PixelRGBA8, PixelRGB8, PixelBaseComponent)
import Control.Monad (forM_)
import Data.Vector.Storable (Vector, unsafeFromForeignPtr0, Storable, slice, concat)
import qualified Graphics.Gloss.Rendering as Gloss
import Graphics.GL
import qualified Graphics.UI.GLFW as GLFW
import Foreign (newForeignPtr_, Ptr)
import Foreign.Marshal.Alloc (free)
import Foreign.Marshal.Array (mallocArray)
import Text.Printf (printf)
import GHC.Int
import qualified Graphics.UI.GLUT as GLUT
import Prelude hiding (concat)
type Size = (Int, Int)
type Animation = Float -> Gloss.Picture
exportPictureToFormat :: (FilePath -> Image PixelRGBA8 -> IO ())
-> Size
-> Gloss.Color
-> FilePath -> Gloss.Picture -> IO ()
exportPictureToFormat savefunc size bgc f p = do
s <- initialize size
(img,ptr) <- pictureToImageRGBA8 size bgc s p
savefunc f img
free ptr
initialize :: Size -> IO Gloss.State
initialize size = do
_ <- GLUT.exit
(_,_) <- GLUT.getArgsAndInitialize
s <- Gloss.initState
initOpenGL size
return s
initOpenGL :: (Int, Int)
-> IO ()
initOpenGL (windowWidth, windowHeight) = do
True <- GLFW.init
Just w <- GLFW.createWindow
windowWidth windowHeight
"gloss-to-file demo"
Nothing Nothing
GLFW.makeContextCurrent (Just w)
exportPicturesToFormat :: (FilePath -> Image PixelRGBA8 -> IO ())
-> Size
-> Gloss.Color
-> FilePath
-> Animation
-> [Float]
-> IO ()
exportPicturesToFormat savefunc size bgc f anim ts = do
s <- initialize size
forM_ (zip [1..] ts) $ \(n, t) -> do
let filename = printf f (n :: Int)
let picture = anim t
(img,ptr) <- pictureToImageRGBA8 size bgc s picture
savefunc filename img
free ptr
pictureToImageRGBA8 :: Size
-> Gloss.Color
-> Gloss.State
-> Gloss.Picture
-> IO (Image PixelRGBA8, Ptr (PixelBaseComponent PixelRGBA8))
pictureToImageRGBA8 (windowWidth, windowHeight) bgc s p = do
drawReadBuffer (windowWidth, windowHeight) bgc s p
imageData <- mallocArray (windowWidth * windowHeight * 4)
let wW = fromIntegral windowWidth :: GHC.Int.Int32
let wH = fromIntegral windowHeight :: GHC.Int.Int32
glReadPixels 0 0 wW wH GL_RGBA GL_UNSIGNED_BYTE imageData
foreignPtr <- newForeignPtr_ imageData
let vector = unsafeFromForeignPtr0 foreignPtr (windowWidth * windowHeight * 4)
let vectorFlipped = reverseImage 4 windowWidth windowHeight vector
let image :: Image PixelRGBA8
image = Image windowWidth windowHeight vectorFlipped
return (image, imageData)
drawReadBuffer :: Size
-> Gloss.Color
-> Gloss.State -> Gloss.Picture -> IO ()
drawReadBuffer size bg s p = do
glDrawBuffer GL_BACK
Gloss.withClearBuffer bg $ Gloss.withModelview size $ do
glColor3f 0 0 0
Gloss.renderPicture s 1 p
glReadBuffer GL_BACK
reverseImage :: Storable a => Int
-> Int
-> Int -> Vector a -> Vector a
reverseImage components width height vec = concat [slice i widthC vec | i <- map (*widthC) [(height-1),(height-2)..0] ]
where
widthC = width*components
pictureToImageRGB8 :: Size
-> Gloss.Color
-> Gloss.State
-> Gloss.Picture
-> IO (Image PixelRGB8, Ptr (PixelBaseComponent PixelRGB8))
pictureToImageRGB8 (windowWidth, windowHeight) bgc s p = do
drawReadBuffer (windowWidth, windowHeight) bgc s p
imageData <- mallocArray (windowWidth * windowHeight * 3)
let wW = fromIntegral windowWidth :: GHC.Int.Int32
let wH = fromIntegral windowHeight :: GHC.Int.Int32
glReadPixels 0 0 wW wH GL_RGB GL_UNSIGNED_BYTE imageData
foreignPtr <- newForeignPtr_ imageData
let vector = unsafeFromForeignPtr0 foreignPtr (windowWidth * windowHeight * 3)
let vectorFlipped = reverseImage 3 windowWidth windowHeight vector
let image :: Image PixelRGB8
image = Image windowWidth windowHeight vectorFlipped
return (image, imageData)