gdritter repos farbfeld / master src / Image / Farbfeld.hs
master

Tree @master (Download .tar.gz)

Farbfeld.hs @masterraw · history · blame

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}

module Image.Farbfeld
  ( Image(..)
  , Pixel(..)
  , parseImage
  , emitImage
  ) where

import           Control.Monad (when, forM_)
import           Data.Array (Array, array, bounds, (!))
import           Data.ByteString.Lazy (ByteString)
import           Data.Word (Word16, Word32)
import qualified Data.Serialize as S

newtype Image = Image
  { imgPixels :: Array (Word32, Word32) Pixel
  } deriving (Eq, Show)

data Pixel = Pixel
  { pxRed   :: !Word16
  , pxGreen :: !Word16
  , pxBlue  :: !Word16
  , pxAlpha :: !Word16
  } deriving (Eq, Show)

parseImage :: ByteString -> Either String Image
parseImage = S.runGetLazy $ do
  magic <- S.getByteString 8
  when (magic /= "farbfeld") $
    fail "Unable to find farbfeld magic number"
  w <- S.getWord32be
  h <- S.getWord32be
  imgPixels <- array ((0, 0), (w-1, h-1)) <$> sequence
    [ sequence ((x, y), getPixel)
    | y <- [0..h-1]
    , x <- [0..w-1]
    ]
  return Image { .. }

emitImage :: Image -> ByteString
emitImage (Image pixels) = S.runPutLazy $ do
  S.putByteString "farbfeld"
  let (w, h) = snd (bounds pixels)
  S.putWord32be (w + 1)
  S.putWord32be (h + 1)
  forM_ [0..h] $ \y ->
    forM_ [0..w] $ \x -> do
      let Pixel { .. } = pixels ! (x, y)
      S.putWord16be pxRed
      S.putWord16be pxGreen
      S.putWord16be pxBlue
      S.putWord16be pxAlpha

getPixel :: S.Get Pixel
getPixel = Pixel
  <$> S.getWord16be
  <*> S.getWord16be
  <*> S.getWord16be
  <*> S.getWord16be