gdritter repos image-vk / master Image / VK.hs
master

Tree @master (Download .tar.gz)

VK.hs @masterraw · history · blame

module Image.VK where

import           Data.ByteString.Lazy (ByteString)
import           Data.Eben (Value(..))
import qualified Data.Eben as Eben

type Point = (Int, Int)

data VKImage = VKImage
  { vkLines :: [[Point]]
  , vkMeta  :: VKMeta
  } deriving (Eq, Show)

data VKMeta = VKMeta { vkSize :: (Int, Int) } deriving (Eq, Show)

catch :: Maybe a -> String -> Either String a
catch (Just a) _ = Right a
catch Nothing  m = Left m

asPoint :: Value -> Either String Point
asPoint v = Eben.fromEben v `catch` "Unable to parse point"

decode :: ByteString -> Either String VKImage
decode bs = do
  (ds, _) <- Eben.decode bs `catch` "Invalid EBEN value"
  metaV   <- Eben.lookup "meta" ds `catch` "Missing field: `meta`"
  (w,h)   <- asPoint metaV
  linesV  <- Eben.lookup "lines" ds `catch` "Missing field: `lines`"
  ls      <- Eben.asList linesV `catch` "`lines` field not a list"
  ls'     <- mapM Eben.asList ls `catch` "arglbargl"
  points  <- sequence [ mapM asPoint l | l <- ls' ]
  return VKImage { vkLines = points
                 , vkMeta = VKMeta { vkSize = (w, h) }
                 }

encode :: VKImage -> ByteString
encode vk = Eben.encode $ Eben.dict
              [ ("meta", Eben.toEben (vkSize (vkMeta vk)))
              , ("lines", Eben.toEben (vkLines vk))
              ]