module DrawTypes where
import Geometry(Point,Rect,Line)
import Xtypes(Pixel,PixmapId,ImageFormat,DbeBackBufferId)
data DrawCommand
= DrawLine Line
| DrawImageString Point String
| DrawString Point String
| DrawRectangle Rect
| FillRectangle Rect
| FillPolygon Shape CoordMode [Point]
| DrawArc Rect Int Int
| FillArc Rect Int Int
| CopyArea Drawable Rect Point
| CopyPlane Drawable Rect Point Int
| DrawPoint Point
| CreatePutImage Rect ImageFormat [Pixel]
| DrawLines CoordMode [Point]
| DrawImageString16 Point String
| DrawString16 Point String
deriving (DrawCommand -> DrawCommand -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DrawCommand -> DrawCommand -> Bool
$c/= :: DrawCommand -> DrawCommand -> Bool
== :: DrawCommand -> DrawCommand -> Bool
$c== :: DrawCommand -> DrawCommand -> Bool
Eq, Eq DrawCommand
DrawCommand -> DrawCommand -> Bool
DrawCommand -> DrawCommand -> Ordering
DrawCommand -> DrawCommand -> DrawCommand
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 :: DrawCommand -> DrawCommand -> DrawCommand
$cmin :: DrawCommand -> DrawCommand -> DrawCommand
max :: DrawCommand -> DrawCommand -> DrawCommand
$cmax :: DrawCommand -> DrawCommand -> DrawCommand
>= :: DrawCommand -> DrawCommand -> Bool
$c>= :: DrawCommand -> DrawCommand -> Bool
> :: DrawCommand -> DrawCommand -> Bool
$c> :: DrawCommand -> DrawCommand -> Bool
<= :: DrawCommand -> DrawCommand -> Bool
$c<= :: DrawCommand -> DrawCommand -> Bool
< :: DrawCommand -> DrawCommand -> Bool
$c< :: DrawCommand -> DrawCommand -> Bool
compare :: DrawCommand -> DrawCommand -> Ordering
$ccompare :: DrawCommand -> DrawCommand -> Ordering
Ord, Int -> DrawCommand -> ShowS
[DrawCommand] -> ShowS
DrawCommand -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DrawCommand] -> ShowS
$cshowList :: [DrawCommand] -> ShowS
show :: DrawCommand -> String
$cshow :: DrawCommand -> String
showsPrec :: Int -> DrawCommand -> ShowS
$cshowsPrec :: Int -> DrawCommand -> ShowS
Show, ReadPrec [DrawCommand]
ReadPrec DrawCommand
Int -> ReadS DrawCommand
ReadS [DrawCommand]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DrawCommand]
$creadListPrec :: ReadPrec [DrawCommand]
readPrec :: ReadPrec DrawCommand
$creadPrec :: ReadPrec DrawCommand
readList :: ReadS [DrawCommand]
$creadList :: ReadS [DrawCommand]
readsPrec :: Int -> ReadS DrawCommand
$creadsPrec :: Int -> ReadS DrawCommand
Read)
data Drawable
= MyWindow
| Pixmap PixmapId
| DbeBackBuffer DbeBackBufferId
deriving (Drawable -> Drawable -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Drawable -> Drawable -> Bool
$c/= :: Drawable -> Drawable -> Bool
== :: Drawable -> Drawable -> Bool
$c== :: Drawable -> Drawable -> Bool
Eq, Eq Drawable
Drawable -> Drawable -> Bool
Drawable -> Drawable -> Ordering
Drawable -> Drawable -> Drawable
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 :: Drawable -> Drawable -> Drawable
$cmin :: Drawable -> Drawable -> Drawable
max :: Drawable -> Drawable -> Drawable
$cmax :: Drawable -> Drawable -> Drawable
>= :: Drawable -> Drawable -> Bool
$c>= :: Drawable -> Drawable -> Bool
> :: Drawable -> Drawable -> Bool
$c> :: Drawable -> Drawable -> Bool
<= :: Drawable -> Drawable -> Bool
$c<= :: Drawable -> Drawable -> Bool
< :: Drawable -> Drawable -> Bool
$c< :: Drawable -> Drawable -> Bool
compare :: Drawable -> Drawable -> Ordering
$ccompare :: Drawable -> Drawable -> Ordering
Ord, Int -> Drawable -> ShowS
[Drawable] -> ShowS
Drawable -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Drawable] -> ShowS
$cshowList :: [Drawable] -> ShowS
show :: Drawable -> String
$cshow :: Drawable -> String
showsPrec :: Int -> Drawable -> ShowS
$cshowsPrec :: Int -> Drawable -> ShowS
Show, ReadPrec [Drawable]
ReadPrec Drawable
Int -> ReadS Drawable
ReadS [Drawable]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Drawable]
$creadListPrec :: ReadPrec [Drawable]
readPrec :: ReadPrec Drawable
$creadPrec :: ReadPrec Drawable
readList :: ReadS [Drawable]
$creadList :: ReadS [Drawable]
readsPrec :: Int -> ReadS Drawable
$creadsPrec :: Int -> ReadS Drawable
Read)
data CoordMode
= CoordModeOrigin
| CoordModePrevious
deriving (CoordMode -> CoordMode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CoordMode -> CoordMode -> Bool
$c/= :: CoordMode -> CoordMode -> Bool
== :: CoordMode -> CoordMode -> Bool
$c== :: CoordMode -> CoordMode -> Bool
Eq, Eq CoordMode
CoordMode -> CoordMode -> Bool
CoordMode -> CoordMode -> Ordering
CoordMode -> CoordMode -> CoordMode
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 :: CoordMode -> CoordMode -> CoordMode
$cmin :: CoordMode -> CoordMode -> CoordMode
max :: CoordMode -> CoordMode -> CoordMode
$cmax :: CoordMode -> CoordMode -> CoordMode
>= :: CoordMode -> CoordMode -> Bool
$c>= :: CoordMode -> CoordMode -> Bool
> :: CoordMode -> CoordMode -> Bool
$c> :: CoordMode -> CoordMode -> Bool
<= :: CoordMode -> CoordMode -> Bool
$c<= :: CoordMode -> CoordMode -> Bool
< :: CoordMode -> CoordMode -> Bool
$c< :: CoordMode -> CoordMode -> Bool
compare :: CoordMode -> CoordMode -> Ordering
$ccompare :: CoordMode -> CoordMode -> Ordering
Ord, Int -> CoordMode -> ShowS
[CoordMode] -> ShowS
CoordMode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CoordMode] -> ShowS
$cshowList :: [CoordMode] -> ShowS
show :: CoordMode -> String
$cshow :: CoordMode -> String
showsPrec :: Int -> CoordMode -> ShowS
$cshowsPrec :: Int -> CoordMode -> ShowS
Show, ReadPrec [CoordMode]
ReadPrec CoordMode
Int -> ReadS CoordMode
ReadS [CoordMode]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CoordMode]
$creadListPrec :: ReadPrec [CoordMode]
readPrec :: ReadPrec CoordMode
$creadPrec :: ReadPrec CoordMode
readList :: ReadS [CoordMode]
$creadList :: ReadS [CoordMode]
readsPrec :: Int -> ReadS CoordMode
$creadsPrec :: Int -> ReadS CoordMode
Read, CoordMode
forall a. a -> a -> Bounded a
maxBound :: CoordMode
$cmaxBound :: CoordMode
minBound :: CoordMode
$cminBound :: CoordMode
Bounded, Int -> CoordMode
CoordMode -> Int
CoordMode -> [CoordMode]
CoordMode -> CoordMode
CoordMode -> CoordMode -> [CoordMode]
CoordMode -> CoordMode -> CoordMode -> [CoordMode]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: CoordMode -> CoordMode -> CoordMode -> [CoordMode]
$cenumFromThenTo :: CoordMode -> CoordMode -> CoordMode -> [CoordMode]
enumFromTo :: CoordMode -> CoordMode -> [CoordMode]
$cenumFromTo :: CoordMode -> CoordMode -> [CoordMode]
enumFromThen :: CoordMode -> CoordMode -> [CoordMode]
$cenumFromThen :: CoordMode -> CoordMode -> [CoordMode]
enumFrom :: CoordMode -> [CoordMode]
$cenumFrom :: CoordMode -> [CoordMode]
fromEnum :: CoordMode -> Int
$cfromEnum :: CoordMode -> Int
toEnum :: Int -> CoordMode
$ctoEnum :: Int -> CoordMode
pred :: CoordMode -> CoordMode
$cpred :: CoordMode -> CoordMode
succ :: CoordMode -> CoordMode
$csucc :: CoordMode -> CoordMode
Enum)
data Shape
= Complex
| Nonconvex
| Convex
deriving (Shape -> Shape -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Shape -> Shape -> Bool
$c/= :: Shape -> Shape -> Bool
== :: Shape -> Shape -> Bool
$c== :: Shape -> Shape -> Bool
Eq, Eq Shape
Shape -> Shape -> Bool
Shape -> Shape -> Ordering
Shape -> Shape -> Shape
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 :: Shape -> Shape -> Shape
$cmin :: Shape -> Shape -> Shape
max :: Shape -> Shape -> Shape
$cmax :: Shape -> Shape -> Shape
>= :: Shape -> Shape -> Bool
$c>= :: Shape -> Shape -> Bool
> :: Shape -> Shape -> Bool
$c> :: Shape -> Shape -> Bool
<= :: Shape -> Shape -> Bool
$c<= :: Shape -> Shape -> Bool
< :: Shape -> Shape -> Bool
$c< :: Shape -> Shape -> Bool
compare :: Shape -> Shape -> Ordering
$ccompare :: Shape -> Shape -> Ordering
Ord, Int -> Shape -> ShowS
[Shape] -> ShowS
Shape -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Shape] -> ShowS
$cshowList :: [Shape] -> ShowS
show :: Shape -> String
$cshow :: Shape -> String
showsPrec :: Int -> Shape -> ShowS
$cshowsPrec :: Int -> Shape -> ShowS
Show, ReadPrec [Shape]
ReadPrec Shape
Int -> ReadS Shape
ReadS [Shape]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Shape]
$creadListPrec :: ReadPrec [Shape]
readPrec :: ReadPrec Shape
$creadPrec :: ReadPrec Shape
readList :: ReadS [Shape]
$creadList :: ReadS [Shape]
readsPrec :: Int -> ReadS Shape
$creadsPrec :: Int -> ReadS Shape
Read, Shape
forall a. a -> a -> Bounded a
maxBound :: Shape
$cmaxBound :: Shape
minBound :: Shape
$cminBound :: Shape
Bounded, Int -> Shape
Shape -> Int
Shape -> [Shape]
Shape -> Shape
Shape -> Shape -> [Shape]
Shape -> Shape -> Shape -> [Shape]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Shape -> Shape -> Shape -> [Shape]
$cenumFromThenTo :: Shape -> Shape -> Shape -> [Shape]
enumFromTo :: Shape -> Shape -> [Shape]
$cenumFromTo :: Shape -> Shape -> [Shape]
enumFromThen :: Shape -> Shape -> [Shape]
$cenumFromThen :: Shape -> Shape -> [Shape]
enumFrom :: Shape -> [Shape]
$cenumFrom :: Shape -> [Shape]
fromEnum :: Shape -> Int
$cfromEnum :: Shape -> Int
toEnum :: Int -> Shape
$ctoEnum :: Int -> Shape
pred :: Shape -> Shape
$cpred :: Shape -> Shape
succ :: Shape -> Shape
$csucc :: Shape -> Shape
Enum)