haskellpngbmpgloss

PNG to BMP in Haskell (for Gloss)


I have PNG files and the Gloss library has a Bitmap constructor for Picture. I can't use loadBMP :: FilePath -> IO Picture because of the filetype, so I'm searching how to load a PNG file, convert it to BMP, and feed it to either bitmapOfBMP :: BMP -> Picture, bitmapOfForeignPtr :: Int -> Int -> ForeignPtr Word8 -> Bool -> Picture or bitmapOfByteString :: Int -> Int -> ByteString -> Bool -> Picture.


Test with JuicyPixels

import Data.ByteString as B
import System.IO as A

import Codec.Picture.Png
import Graphics.Gloss.Interface.Pure.Game


main = do
    png <- B.readFile "samus.png"
    let img = decodePng png
    case img of
        Left x -> A.putStrLn x
        Right x -> do
            let bmp = encodeDynamicPng x
            case bmp of
                Left x -> A.putStrLn x
                Right x -> do
                    let pic = bitmapOfByteString 29 52 x True
                    game pic

game pic
    =  play
        (InWindow "Test" (700, 500) (10, 10))
        white
        30
        pic
        draw
        (const id)
        (const id)

draw bmp
    = bmp

Everything succeeds but the image is not the same at all.


Solution

  • Even though I didn't come with the answer alone, but thanks to Thomas' answer, I will post it here instead of inside the question.

    As a reminder, the goal is to convert a BMP file into a Gloss' Picture, so I wrote a function called bmpToPic. I put it in a module, because it uses two others functions, and needs many imports. Also, repaToPicture from Thomas' answer is slighty different here.

    module PngToPic
        (pngToPic)
        where
    
    import Data.ByteString as B
    import Data.Word
    
    import Codec.Picture.Png
    import Codec.Picture.Repa
    import qualified Data.ByteString.Internal as BI
    import Data.Array.Repa ((:.)(..), Z, Z(..), extent, DIM3, Array)
    import qualified Data.Array.Repa as R
    import qualified Data.Array.Repa.Repr.ForeignPtr as F
    import Graphics.Gloss.Data.Picture
    
    
    pngToPic :: ByteString -> Picture
    pngToPic png
        = let
            Right img -- unsafe
                = decodePng png
            repa
                = imgData (convertImage img :: Img RGBA)
        in repaToPicture True repa
    
    repaToPicture :: Bool -> Array F.F DIM3 Word8 -> Picture
    repaToPicture b arr
        = bitmapOfByteString row col bs b
        where
            bs
                = BI.fromForeignPtr fptr 0 (R.size sh)
            fptr
                = F.toForeignPtr arr'
            sh@(Z :. col :. row :. depth)
                = extent arr'
            arr'
                = flipVert arr
    
    flipVert :: Array F.F DIM3 Word8 -> Array F.F DIM3 Word8
    flipVert g
        = R.computeS $ R.backpermute e flop g
        where
            e@(Z :. x :. y :. _)
                = extent g
            flop (Z :. i         :. j         :. k)
                = Z :. x - i - 1 :. j :. k
    

    You use it like that:

    import Data.ByteString as B
    
    import Graphics.Gloss.Interface.Pure.Game
    
    import PngToPic
    
    main = do
        png <- B.readFile "someImage.png"
        game $ pngToPic png
    
    game pic
        = play
            (InWindow "Test" (700, 500) (10, 10))
            white
            30
            pic
            id
            (const id)
            (const id)
    

    and the image will show up in the middle of the window.