{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module CodeWorld.Picture where
import CodeWorld.Color
import Control.DeepSeq
import Data.List
import Data.Monoid ((<>))
import Data.Text (Text)
import GHC.Generics (Generic)
import GHC.Stack
import Util.EmbedAsUrl
type Point = (Double, Double)
translatedPoint :: Double -> Double -> Point -> Point
translatedPoint tx ty (x, y) = (x + tx, y + ty)
rotatedPoint :: Double -> Point -> Point
rotatedPoint = rotatedVector
reflectedPoint :: Double -> Point -> Point
reflectedPoint th (x, y) = (x * cos a + y * sin a, x * sin a - y * cos a)
where a = 2 * th
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*x + y*y)
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
data Picture
= SolidPolygon (Maybe SrcLoc) [Point]
| SolidClosedCurve (Maybe SrcLoc) [Point]
| Polygon (Maybe SrcLoc) [Point]
| ThickPolygon (Maybe SrcLoc) [Point] !Double
| Rectangle (Maybe SrcLoc) !Double !Double
| SolidRectangle (Maybe SrcLoc) !Double !Double
| ThickRectangle (Maybe SrcLoc) !Double !Double !Double
| ClosedCurve (Maybe SrcLoc) [Point]
| ThickClosedCurve (Maybe SrcLoc) [Point] !Double
| Polyline (Maybe SrcLoc) [Point]
| ThickPolyline (Maybe SrcLoc) [Point] !Double
| Curve (Maybe SrcLoc) [Point]
| ThickCurve (Maybe SrcLoc) [Point] !Double
| Circle (Maybe SrcLoc) !Double
| SolidCircle (Maybe SrcLoc) !Double
| ThickCircle (Maybe SrcLoc) !Double !Double
| Sector (Maybe SrcLoc) !Double !Double !Double
| Arc (Maybe SrcLoc) !Double !Double !Double
| ThickArc (Maybe SrcLoc) !Double !Double !Double !Double
| StyledLettering (Maybe SrcLoc) !TextStyle !Font !Text
| Lettering (Maybe SrcLoc) !Text
| Color (Maybe SrcLoc) !Color !Picture
| Translate (Maybe SrcLoc) !Double !Double !Picture
| Scale (Maybe SrcLoc) !Double !Double !Picture
| Dilate (Maybe SrcLoc) !Double !Picture
| Rotate (Maybe SrcLoc) !Double !Picture
| Reflect (Maybe SrcLoc) !Double !Picture
| Clip (Maybe SrcLoc) !Double !Double !Picture
| CoordinatePlane (Maybe SrcLoc)
| Sketch (Maybe SrcLoc) !Text !Text !Double !Double
| Pictures (Maybe SrcLoc) [Picture]
| PictureAnd (Maybe SrcLoc) [Picture]
| Blank (Maybe SrcLoc)
deriving (Generic)
instance NFData Picture
data TextStyle
= Plain
| Bold
| Italic
deriving (Generic, Show)
instance NFData TextStyle
data Font
= SansSerif
| Serif
| Monospace
| Handwriting
| Fancy
| NamedFont !Text
deriving (Generic, Show)
instance NFData Font
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 2020."] #-}
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 2020."] #-}
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)
{-# WARNING text ["Please used lettering instead of text.",
"text may be removed July 2020."] #-}
lettering :: HasCallStack => Text -> Picture
lettering = Lettering (getDebugSrcLoc callStack)
styledText :: HasCallStack => TextStyle -> Font -> Text -> Picture
styledText = StyledLettering (getDebugSrcLoc callStack)
{-# WARNING styledText ["Please used styledLettering instead of styledText.",
"styledText may be removed July 2020."] #-}
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)
reflected :: HasCallStack => Double -> Picture -> Picture
reflected = Reflect (getDebugSrcLoc callStack)
clipped :: HasCallStack => Double -> Double -> Picture -> Picture
clipped = Clip (getDebugSrcLoc callStack)
pictures :: HasCallStack => [Picture] -> Picture
pictures = Pictures (getDebugSrcLoc callStack)
(&) :: HasCallStack => Picture -> Picture -> Picture
infixr 0 &
a & PictureAnd loc2 bs
| srcContains loc1 loc2 = PictureAnd loc1 (a:bs)
where loc1 = getDebugSrcLoc callStack
a & b = PictureAnd (getDebugSrcLoc callStack) [a, b]
instance Monoid Picture where
mempty = blank
mappend = (&)
mconcat = pictures
#if MIN_VERSION_base(4,11,0)
instance Semigroup Picture where
(<>) = (&)
#endif
coordinatePlane :: HasCallStack => Picture
coordinatePlane = CoordinatePlane (getDebugSrcLoc callStack)
codeWorldLogo :: HasCallStack => Picture
codeWorldLogo =
Sketch
(getDebugSrcLoc callStack)
"codeWorldLogo"
$(embedAsUrl "image/svg+xml" "data/codeworld.svg")
17.68 7.28
image
:: HasCallStack
=> Text
-> Text
-> Double
-> Double
-> Picture
image = Sketch (getDebugSrcLoc callStack)
getDebugSrcLoc :: CallStack -> Maybe SrcLoc
getDebugSrcLoc cs = Data.List.find ((== "main") . srcLocPackage) locs
where
locs = map snd (getCallStack cs)
srcContains :: Maybe SrcLoc -> Maybe SrcLoc -> Bool
srcContains Nothing _ = False
srcContains _ Nothing = True
srcContains (Just a) (Just b) =
srcLocFile a == srcLocFile b && srcLocStartLine a < srcLocStartLine b ||
(srcLocStartLine a == srcLocStartLine b &&
srcLocStartCol a <= srcLocStartCol b) &&
srcLocEndLine a > srcLocEndLine b ||
(srcLocEndLine a == srcLocEndLine b && srcLocEndCol a >= srcLocEndCol b)