{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE ExistentialQuantification #-}
module Patat.Images.Internal
( Config (..)
, Backend (..)
, BackendNotSupported (..)
, Handle (..)
) where
import Control.Exception (Exception)
import qualified Data.Aeson as A
import Data.Data (Data)
import Data.Typeable (Typeable)
import Patat.Cleanup
data Config a = Auto | Explicit a deriving (Config a -> Config a -> Bool
forall a. Eq a => Config a -> Config a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Config a -> Config a -> Bool
$c/= :: forall a. Eq a => Config a -> Config a -> Bool
== :: Config a -> Config a -> Bool
$c== :: forall a. Eq a => Config a -> Config a -> Bool
Eq)
data Backend = forall a. A.FromJSON a => Backend (Config a -> IO Handle)
data BackendNotSupported = BackendNotSupported String
deriving (Typeable BackendNotSupported
BackendNotSupported -> DataType
BackendNotSupported -> Constr
(forall b. Data b => b -> b)
-> BackendNotSupported -> BackendNotSupported
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> BackendNotSupported -> u
forall u.
(forall d. Data d => d -> u) -> BackendNotSupported -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BackendNotSupported -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BackendNotSupported -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> BackendNotSupported -> m BackendNotSupported
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> BackendNotSupported -> m BackendNotSupported
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BackendNotSupported
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> BackendNotSupported
-> c BackendNotSupported
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BackendNotSupported)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c BackendNotSupported)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> BackendNotSupported -> m BackendNotSupported
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> BackendNotSupported -> m BackendNotSupported
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> BackendNotSupported -> m BackendNotSupported
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> BackendNotSupported -> m BackendNotSupported
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> BackendNotSupported -> m BackendNotSupported
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> BackendNotSupported -> m BackendNotSupported
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> BackendNotSupported -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> BackendNotSupported -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> BackendNotSupported -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> BackendNotSupported -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BackendNotSupported -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BackendNotSupported -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BackendNotSupported -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BackendNotSupported -> r
gmapT :: (forall b. Data b => b -> b)
-> BackendNotSupported -> BackendNotSupported
$cgmapT :: (forall b. Data b => b -> b)
-> BackendNotSupported -> BackendNotSupported
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c BackendNotSupported)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c BackendNotSupported)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BackendNotSupported)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BackendNotSupported)
dataTypeOf :: BackendNotSupported -> DataType
$cdataTypeOf :: BackendNotSupported -> DataType
toConstr :: BackendNotSupported -> Constr
$ctoConstr :: BackendNotSupported -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BackendNotSupported
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BackendNotSupported
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> BackendNotSupported
-> c BackendNotSupported
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> BackendNotSupported
-> c BackendNotSupported
Data, Int -> BackendNotSupported -> ShowS
[BackendNotSupported] -> ShowS
BackendNotSupported -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BackendNotSupported] -> ShowS
$cshowList :: [BackendNotSupported] -> ShowS
show :: BackendNotSupported -> String
$cshow :: BackendNotSupported -> String
showsPrec :: Int -> BackendNotSupported -> ShowS
$cshowsPrec :: Int -> BackendNotSupported -> ShowS
Show, Typeable)
instance Exception BackendNotSupported
data Handle = Handle
{ Handle -> String -> IO Cleanup
hDrawImage :: FilePath -> IO Cleanup
}