{-# LANGUAGE CPP #-}
module CodeWorld.Picture where
import CodeWorld.Color
import Data.List
import Data.Monoid ((<>))
import Data.Text (Text, pack)
import GHC.Stack
type Point = (Double, Double)
translatedPoint :: Double -> Double -> Point -> Point
translatedPoint tx ty (x, y) = (x + tx, y + ty)
rotatedPoint :: Double -> Point -> Point
rotatedPoint = rotatedVector
scaledPoint :: Double -> Double -> Point -> Point
scaledPoint kx ky (x, y) = (kx * x, ky * y)
dilatedPoint :: Double -> Point -> Point
dilatedPoint k (x, y) = (k * x, k * y)
type Vector = (Double, Double)
vectorLength :: Vector -> Double
vectorLength (x, y) = sqrt (x ^ 2 + y ^ 2)
vectorDirection :: Vector -> Double
vectorDirection (x, y) = atan2 y x
vectorSum :: Vector -> Vector -> Vector
vectorSum (x1, y1) (x2, y2) = (x1 + x2, y1 + y2)
vectorDifference :: Vector -> Vector -> Vector
vectorDifference (x1, y1) (x2, y2) = (x1 - x2, y1 - y2)
scaledVector :: Double -> Vector -> Vector
scaledVector k (x, y) = (k * x, k * y)
rotatedVector :: Double -> Vector -> Vector
rotatedVector angle (x, y) =
(x * cos angle - y * sin angle, x * sin angle + y * cos angle)
dotProduct :: Vector -> Vector -> Double
dotProduct (x1, y1) (x2, y2) = x1 * x2 + y1 * y2
getDebugSrcLoc :: CallStack -> SrcLoc
getDebugSrcLoc cs =
case Data.List.find ((== "main") . srcLocPackage) locs of
Just loc -> loc
Nothing -> error "Cannot find debug source location."
where
locs = map snd (getCallStack cs)
data Picture
= SolidPolygon SrcLoc
[Point]
| SolidClosedCurve SrcLoc
[Point]
| Polygon SrcLoc
[Point]
| ThickPolygon SrcLoc
[Point]
!Double
| Rectangle SrcLoc
!Double
!Double
| SolidRectangle SrcLoc
!Double
!Double
| ThickRectangle SrcLoc
!Double
!Double
!Double
| ClosedCurve SrcLoc
[Point]
| ThickClosedCurve SrcLoc
[Point]
!Double
| Polyline SrcLoc
[Point]
| ThickPolyline SrcLoc
[Point]
!Double
| Curve SrcLoc
[Point]
| ThickCurve SrcLoc
[Point]
!Double
| Circle SrcLoc
!Double
| SolidCircle SrcLoc
!Double
| ThickCircle SrcLoc
!Double
!Double
| Sector SrcLoc
!Double
!Double
!Double
| Arc SrcLoc
!Double
!Double
!Double
| ThickArc SrcLoc
!Double
!Double
!Double
!Double
| StyledLettering SrcLoc
!TextStyle
!Font
!Text
| Lettering SrcLoc
!Text
| Color SrcLoc
!Color
!Picture
| Translate SrcLoc
!Double
!Double
!Picture
| Scale SrcLoc
!Double
!Double
!Picture
| Dilate SrcLoc
!Double
!Picture
| Rotate SrcLoc
!Double
!Picture
| CoordinatePlane SrcLoc
| Logo SrcLoc
| Pictures [Picture]
| Blank SrcLoc
data TextStyle
= Plain
| Bold
| Italic deriving (Show)
data Font
= SansSerif
| Serif
| Monospace
| Handwriting
| Fancy
| NamedFont !Text deriving (Show)
blank :: HasCallStack => Picture
blank = Blank (getDebugSrcLoc callStack)
polyline :: HasCallStack => [Point] -> Picture
polyline ps = Polyline (getDebugSrcLoc callStack) ps
path :: HasCallStack => [Point] -> Picture
path ps = Polyline (getDebugSrcLoc callStack) ps
{-# WARNING path ["Please use polyline instead of path.",
"path may be removed July 2019."] #-}
thickPolyline :: HasCallStack => Double -> [Point] -> Picture
thickPolyline n ps = ThickPolyline (getDebugSrcLoc callStack) ps n
thickPath :: HasCallStack => Double -> [Point] -> Picture
thickPath n ps = ThickPolyline (getDebugSrcLoc callStack) ps n
{-# WARNING thickPath ["Please used thickPolyline instead of thickPath.",
"thickPath may be removed July 2019."] #-}
polygon :: HasCallStack => [Point] -> Picture
polygon ps = Polygon (getDebugSrcLoc callStack) ps
thickPolygon :: HasCallStack => Double -> [Point] -> Picture
thickPolygon n ps = ThickPolygon (getDebugSrcLoc callStack) ps n
solidPolygon :: HasCallStack => [Point] -> Picture
solidPolygon ps = SolidPolygon (getDebugSrcLoc callStack) ps
curve :: HasCallStack => [Point] -> Picture
curve ps = Curve (getDebugSrcLoc callStack) ps
thickCurve :: HasCallStack => Double -> [Point] -> Picture
thickCurve n ps = ThickCurve (getDebugSrcLoc callStack) ps n
closedCurve :: HasCallStack => [Point] -> Picture
closedCurve ps = ClosedCurve (getDebugSrcLoc callStack) ps
thickClosedCurve :: HasCallStack => Double -> [Point] -> Picture
thickClosedCurve n ps = ThickClosedCurve (getDebugSrcLoc callStack) ps n
solidClosedCurve :: HasCallStack => [Point] -> Picture
solidClosedCurve ps = SolidClosedCurve (getDebugSrcLoc callStack) ps
rectangleVertices :: Double -> Double -> [Point]
rectangleVertices w h = [ (w / 2, h / 2), (w / 2, -h / 2), (-w / 2, -h / 2), (-w / 2, h / 2) ]
rectangle :: HasCallStack => Double -> Double -> Picture
rectangle w h = Rectangle (getDebugSrcLoc callStack) w h
solidRectangle :: HasCallStack => Double -> Double -> Picture
solidRectangle w h = SolidRectangle (getDebugSrcLoc callStack) w h
thickRectangle :: HasCallStack => Double -> Double -> Double -> Picture
thickRectangle lw w h = ThickRectangle (getDebugSrcLoc callStack) lw w h
circle :: HasCallStack => Double -> Picture
circle = Circle (getDebugSrcLoc callStack)
thickCircle :: HasCallStack => Double -> Double -> Picture
thickCircle = ThickCircle (getDebugSrcLoc callStack)
arc :: HasCallStack => Double -> Double -> Double -> Picture
arc b e r = Arc (getDebugSrcLoc callStack) b e r
thickArc :: HasCallStack => Double -> Double -> Double -> Double -> Picture
thickArc w b e r = ThickArc (getDebugSrcLoc callStack) b e r w
solidCircle :: HasCallStack => Double -> Picture
solidCircle = SolidCircle (getDebugSrcLoc callStack)
sector :: HasCallStack => Double -> Double -> Double -> Picture
sector = Sector (getDebugSrcLoc callStack)
text :: HasCallStack => Text -> Picture
text = Lettering (getDebugSrcLoc callStack)
lettering :: HasCallStack => Text -> Picture
lettering = Lettering (getDebugSrcLoc callStack)
styledText :: HasCallStack => TextStyle -> Font -> Text -> Picture
styledText = StyledLettering (getDebugSrcLoc callStack)
styledLettering :: HasCallStack => TextStyle -> Font -> Text -> Picture
styledLettering = StyledLettering (getDebugSrcLoc callStack)
colored :: HasCallStack => Color -> Picture -> Picture
colored = Color (getDebugSrcLoc callStack)
coloured :: HasCallStack => Color -> Picture -> Picture
coloured = colored
translated :: HasCallStack => Double -> Double -> Picture -> Picture
translated = Translate (getDebugSrcLoc callStack)
scaled :: HasCallStack => Double -> Double -> Picture -> Picture
scaled = Scale (getDebugSrcLoc callStack)
dilated :: HasCallStack => Double -> Picture -> Picture
dilated = Dilate (getDebugSrcLoc callStack)
rotated :: HasCallStack => Double -> Picture -> Picture
rotated = Rotate (getDebugSrcLoc callStack)
pictures :: [Picture] -> Picture
pictures = Pictures
#if MIN_VERSION_base(4,11,0)
instance Semigroup Picture where
a <> (Pictures bs) = Pictures (a : bs)
a <> b = Pictures [a, b]
#endif
instance Monoid Picture where
mempty = blank
mappend a (Pictures bs) = Pictures (a : bs)
mappend a b = Pictures [a, b]
mconcat = pictures
(&) :: Picture -> Picture -> Picture
infixr 0 &
(&) = mappend
coordinatePlane :: HasCallStack => Picture
coordinatePlane = CoordinatePlane (getDebugSrcLoc callStack)
codeWorldLogo :: HasCallStack => Picture
codeWorldLogo = Logo (getDebugSrcLoc callStack)