module Image where

newtype ImageFormat = ImageFormat Int deriving (ImageFormat -> ImageFormat -> Bool
(ImageFormat -> ImageFormat -> Bool)
-> (ImageFormat -> ImageFormat -> Bool) -> Eq ImageFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImageFormat -> ImageFormat -> Bool
$c/= :: ImageFormat -> ImageFormat -> Bool
== :: ImageFormat -> ImageFormat -> Bool
$c== :: ImageFormat -> ImageFormat -> Bool
Eq, Eq ImageFormat
Eq ImageFormat
-> (ImageFormat -> ImageFormat -> Ordering)
-> (ImageFormat -> ImageFormat -> Bool)
-> (ImageFormat -> ImageFormat -> Bool)
-> (ImageFormat -> ImageFormat -> Bool)
-> (ImageFormat -> ImageFormat -> Bool)
-> (ImageFormat -> ImageFormat -> ImageFormat)
-> (ImageFormat -> ImageFormat -> ImageFormat)
-> Ord ImageFormat
ImageFormat -> ImageFormat -> Bool
ImageFormat -> ImageFormat -> Ordering
ImageFormat -> ImageFormat -> ImageFormat
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ImageFormat -> ImageFormat -> ImageFormat
$cmin :: ImageFormat -> ImageFormat -> ImageFormat
max :: ImageFormat -> ImageFormat -> ImageFormat
$cmax :: ImageFormat -> ImageFormat -> ImageFormat
>= :: ImageFormat -> ImageFormat -> Bool
$c>= :: ImageFormat -> ImageFormat -> Bool
> :: ImageFormat -> ImageFormat -> Bool
$c> :: ImageFormat -> ImageFormat -> Bool
<= :: ImageFormat -> ImageFormat -> Bool
$c<= :: ImageFormat -> ImageFormat -> Bool
< :: ImageFormat -> ImageFormat -> Bool
$c< :: ImageFormat -> ImageFormat -> Bool
compare :: ImageFormat -> ImageFormat -> Ordering
$ccompare :: ImageFormat -> ImageFormat -> Ordering
$cp1Ord :: Eq ImageFormat
Ord, ReadPrec [ImageFormat]
ReadPrec ImageFormat
Int -> ReadS ImageFormat
ReadS [ImageFormat]
(Int -> ReadS ImageFormat)
-> ReadS [ImageFormat]
-> ReadPrec ImageFormat
-> ReadPrec [ImageFormat]
-> Read ImageFormat
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ImageFormat]
$creadListPrec :: ReadPrec [ImageFormat]
readPrec :: ReadPrec ImageFormat
$creadPrec :: ReadPrec ImageFormat
readList :: ReadS [ImageFormat]
$creadList :: ReadS [ImageFormat]
readsPrec :: Int -> ReadS ImageFormat
$creadsPrec :: Int -> ReadS ImageFormat
Read, Int -> ImageFormat -> ShowS
[ImageFormat] -> ShowS
ImageFormat -> String
(Int -> ImageFormat -> ShowS)
-> (ImageFormat -> String)
-> ([ImageFormat] -> ShowS)
-> Show ImageFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImageFormat] -> ShowS
$cshowList :: [ImageFormat] -> ShowS
show :: ImageFormat -> String
$cshow :: ImageFormat -> String
showsPrec :: Int -> ImageFormat -> ShowS
$cshowsPrec :: Int -> ImageFormat -> ShowS
Show)

xyBitmap :: ImageFormat
xyBitmap = Int -> ImageFormat
ImageFormat Int
0
xyPixmap :: ImageFormat
xyPixmap = Int -> ImageFormat
ImageFormat Int
1
zPixmap :: ImageFormat
zPixmap  = Int -> ImageFormat
ImageFormat Int
2