module Drawcmd(move, moveDrawCommands, moveDrawCommand) where
import DrawTypes
import Geometry(Move(..))
instance Move DrawCommand where move :: Point -> DrawCommand -> DrawCommand
move = forall a b c. (a -> b -> c) -> b -> a -> c
flip DrawCommand -> Point -> DrawCommand
moveDrawCommand
moveDrawCommand :: DrawCommand -> Point -> DrawCommand
moveDrawCommand DrawCommand
cmd Point
v =
case DrawCommand
cmd of
DrawLine Line
l -> Line -> DrawCommand
DrawLine (forall a. Move a => Point -> a -> a
move Point
v Line
l)
DrawLines CoordMode
cm [Point]
ps -> CoordMode -> [Point] -> DrawCommand
DrawLines CoordMode
cm (forall {a}. Move a => CoordMode -> [a] -> Point -> [a]
movePoints CoordMode
cm [Point]
ps Point
v)
DrawImageString Point
p String
s -> Point -> String -> DrawCommand
DrawImageString (forall a. Move a => Point -> a -> a
move Point
v Point
p) String
s
DrawString Point
p String
s -> Point -> String -> DrawCommand
DrawString (forall a. Move a => Point -> a -> a
move Point
v Point
p) String
s
DrawRectangle Rect
r -> Rect -> DrawCommand
DrawRectangle (forall a. Move a => Point -> a -> a
move Point
v Rect
r)
FillRectangle Rect
r -> Rect -> DrawCommand
FillRectangle (forall a. Move a => Point -> a -> a
move Point
v Rect
r)
FillPolygon Shape
shape CoordMode
coordMode [Point]
ps ->
Shape -> CoordMode -> [Point] -> DrawCommand
FillPolygon Shape
shape CoordMode
coordMode (forall {a}. Move a => CoordMode -> [a] -> Point -> [a]
movePoints CoordMode
coordMode [Point]
ps Point
v)
DrawArc Rect
r Int
a1 Int
a2 -> Rect -> Int -> Int -> DrawCommand
DrawArc (forall a. Move a => Point -> a -> a
move Point
v Rect
r) Int
a1 Int
a2
FillArc Rect
r Int
a1 Int
a2 -> Rect -> Int -> Int -> DrawCommand
FillArc (forall a. Move a => Point -> a -> a
move Point
v Rect
r) Int
a1 Int
a2
CopyArea Drawable
d Rect
r Point
p -> Drawable -> Rect -> Point -> DrawCommand
CopyArea Drawable
d Rect
r (forall a. Move a => Point -> a -> a
move Point
v Point
p)
CopyPlane Drawable
d Rect
r Point
p Int
n -> Drawable -> Rect -> Point -> Int -> DrawCommand
CopyPlane Drawable
d Rect
r (forall a. Move a => Point -> a -> a
move Point
v Point
p) Int
n
DrawPoint Point
p -> Point -> DrawCommand
DrawPoint (forall a. Move a => Point -> a -> a
move Point
v Point
p)
CreatePutImage Rect
r ImageFormat
fmt [Pixel]
pxls -> Rect -> ImageFormat -> [Pixel] -> DrawCommand
CreatePutImage (forall a. Move a => Point -> a -> a
move Point
v Rect
r) ImageFormat
fmt [Pixel]
pxls
DrawImageString16 Point
p String
s -> Point -> String -> DrawCommand
DrawImageString16 (forall a. Move a => Point -> a -> a
move Point
v Point
p) String
s
DrawString16 Point
p String
s -> Point -> String -> DrawCommand
DrawString16 (forall a. Move a => Point -> a -> a
move Point
v Point
p) String
s
movePoints :: CoordMode -> [a] -> Point -> [a]
movePoints CoordMode
cm [a]
ps Point
v =
case CoordMode
cm of
CoordMode
CoordModeOrigin -> forall a. Move a => Point -> a -> a
move Point
v [a]
ps
CoordMode
CoordModePrevious ->
case [a]
ps of
a
p:[a]
ps' -> forall a. Move a => Point -> a -> a
move Point
v a
pforall a. a -> [a] -> [a]
:[a]
ps'
[] -> []
moveDrawCommands :: [DrawCommand] -> Point -> [DrawCommand]
moveDrawCommands [DrawCommand]
cmds Point
p = forall a b. (a -> b) -> [a] -> [b]
map (DrawCommand -> Point -> DrawCommand
`moveDrawCommand` Point
p) [DrawCommand]
cmds