{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.Massiv.Array.IO.Base
( FileFormat(..)
, Readable(..)
, Writable(..)
, ConvertError(..)
, EncodeError(..)
, DecodeError(..)
, Sequence(..)
, Auto(..)
, Image
, defaultReadOptions
, defaultWriteOptions
, toProxy
, fromMaybeEncode
, fromEitherDecode
, convertEither
) where
import Control.Exception (Exception, throw)
import qualified Data.ByteString as B (ByteString)
import qualified Data.ByteString.Lazy as BL (ByteString)
import Data.Default.Class (Default(..))
import Data.Massiv.Array
import Data.Maybe (fromMaybe)
import Data.Typeable
import Graphics.ColorSpace (ColorSpace, Pixel)
type Image r cs e = Array r Ix2 (Pixel cs e)
newtype ConvertError = ConvertError String deriving Show
instance Exception ConvertError
newtype DecodeError = DecodeError String deriving Show
instance Exception DecodeError
newtype EncodeError = EncodeError String deriving Show
instance Exception EncodeError
defaultReadOptions :: FileFormat f => f -> ReadOptions f
defaultReadOptions _ = def
defaultWriteOptions :: FileFormat f => f -> WriteOptions f
defaultWriteOptions _ = def
newtype Sequence f = Sequence f deriving Show
newtype Auto f = Auto f deriving Show
class (Default (ReadOptions f), Default (WriteOptions f), Show f) => FileFormat f where
type ReadOptions f
type ReadOptions f = ()
type WriteOptions f
type WriteOptions f = ()
ext :: f -> String
exts :: f -> [String]
exts f = [ext f]
isFormat :: String -> f -> Bool
isFormat e f = e `elem` exts f
instance FileFormat f => FileFormat (Auto f) where
type ReadOptions (Auto f) = ReadOptions f
type WriteOptions (Auto f) = WriteOptions f
ext (Auto f) = ext f
exts (Auto f) = exts f
class Readable f arr where
decode :: f -> ReadOptions f -> B.ByteString -> arr
class Writable f arr where
encode :: f -> WriteOptions f -> arr -> BL.ByteString
toProxy :: a -> Proxy a
toProxy _ = Proxy
fromMaybeEncode
:: forall f r cs e b. (ColorSpace cs e, FileFormat f, Typeable r)
=> f -> Proxy (Image r cs e) -> Maybe b -> b
fromMaybeEncode _ _ (Just b) = b
fromMaybeEncode f _imgProxy Nothing =
throw $
ConvertError
("Format " ++
show f ++
" cannot be encoded as <Image " ++
showsTypeRep (typeRep (Proxy :: Proxy r)) " " ++
showsTypeRep (typeRep (Proxy :: Proxy cs)) " " ++
showsTypeRep (typeRep (Proxy :: Proxy e)) ">")
fromEitherDecode :: forall r cs e a f. (ColorSpace cs e, FileFormat f, Typeable r) =>
f
-> (a -> String)
-> (a -> Maybe (Image r cs e))
-> Either String a
-> Image r cs e
fromEitherDecode _ _ _ (Left err) = throw $ DecodeError err
fromEitherDecode f showCS conv (Right eImg) =
fromMaybe
(throw $
ConvertError
("Cannot decode " ++ show f ++ " image <" ++
showCS eImg ++
"> as " ++
"<Image " ++
showsTypeRep (typeRep (Proxy :: Proxy r)) " " ++
showsTypeRep (typeRep (Proxy :: Proxy cs)) " " ++
showsTypeRep (typeRep (Proxy :: Proxy e)) ">"))
(conv eImg)
convertEither :: forall r cs e a f. (ColorSpace cs e, FileFormat f, Typeable r) =>
f
-> (a -> String)
-> (a -> Maybe (Image r cs e))
-> a
-> Either ConvertError (Image r cs e)
convertEither f showCS conv eImg =
maybe
(Left $
ConvertError
("Cannot convert " ++ show f ++ " image <" ++
showCS eImg ++
"> as " ++
"<Image " ++
showsTypeRep (typeRep (Proxy :: Proxy r)) " " ++
showsTypeRep (typeRep (Proxy :: Proxy cs)) " " ++
showsTypeRep (typeRep (Proxy :: Proxy e)) ">"))
Right
(conv eImg)