{-# LANGUAGE DeriveDataTypeable #-}
module Picture
( Picture(..)
, Point
, Vector
, Path
, Source(..)
, lineLoop
, sectorWire
, rectanglePath
, rectangleWire
, rectangleSolid
)
where
import Data.Monoid
import Data.Semigroup
import Data.Foldable
import Color
import Text
type Point = (Double, Double)
type Vector = Point
type Path = [Point]
data Source =
File String
| Url String
deriving (Show, Eq)
data Picture
= Blank
| Line Path
| Polygon Path
| Circle Double
| Arc Double Double Double
| Rectangle Double Double
| Image Source Double Double
| Text String Font FontSize
| Color Color Picture
| Stroke Color Double Picture
| Translate Double Double Picture
| Scale Double Double Picture
| Pictures [Picture]
deriving (Show, Eq)
instance Monoid Picture where
mempty = Blank
mappend a b = Pictures [a, b]
mconcat = Pictures
instance Semigroup Picture where
a <> b = Pictures [a, b]
sconcat = Pictures . toList
stimes = stimesIdempotent
lineLoop :: Path -> Picture
lineLoop [] = Line []
lineLoop (x : xs) = Line ((x : xs) ++ [x])
sectorWire :: Double -> Double -> Double -> Picture
sectorWire a1 a2 r_ =
let r = abs r_
in Pictures
[ Arc a1 a2 r
, Line [(0, 0), (r * cos (degToRad a1), r * sin (degToRad a1))]
, Line [(0, 0), (r * cos (degToRad a2), r * sin (degToRad a2))]
]
rectanglePath
:: Double
-> Double
-> Path
rectanglePath sizeX sizeY =
let sx = sizeX / 2
sy = sizeY / 2
in [(-sx, -sy), (-sx, sy), (sx, sy), (sx, -sy)]
rectangleWire :: Double -> Double -> Picture
rectangleWire sizeX sizeY = lineLoop $ rectanglePath sizeX sizeY
rectangleSolid
:: Double
-> Double
-> Picture
rectangleSolid sizeX sizeY = Polygon $ rectanglePath sizeX sizeY
degToRad :: Double -> Double
degToRad d = d * pi / 180
{-# INLINE degToRad #-}
radToDeg :: Double -> Double
radToDeg r = r * 180 / pi
{-# INLINE radToDeg #-}
normalizeAngle :: Double -> Double
normalizeAngle f = f - 2 * pi * floor' (f / (2 * pi))
where
floor' :: Double -> Double
floor' x = fromIntegral (floor x :: Int)