module Graphics.Rendering.Plot.Light.Internal (Frame(..), Point(..), LabeledPoint(..), Axis(..), svgHeader, rectCentered, circle, line, tick, ticks, axis, text, polyline, strokeLineJoin, LineStroke_(..), StrokeLineJoin_(..), TextAnchor_(..), V2(..), Mat2(..), DiagMat2(..), diagMat2, AdditiveGroup(..), VectorSpace(..), Hermitian(..), LinearMap(..), MultiplicativeSemigroup(..), MatrixGroup(..), Eps(..), norm2, normalize2, v2fromEndpoints, v2fromPoint, origin, movePoint, moveLabeledPointV2, fromUnitSquare, toUnitSquare, e1, e2) where
import Data.Monoid ((<>))
import qualified Data.Foldable as F (toList)
import Data.List
import Control.Arrow ((&&&), (***))
import Control.Monad (forM, forM_)
import Data.Semigroup (Min(..), Max(..))
import Data.Scientific (Scientific, toRealFloat)
import qualified Data.Text as T
import Text.Blaze.Svg
import Text.Blaze.Svg11 ((!))
import qualified Text.Blaze.Svg11 as S hiding (style)
import qualified Text.Blaze.Svg11.Attributes as SA hiding (rotate)
import Text.Blaze.Svg.Renderer.String (renderSvg)
import qualified Data.Colour as C
import qualified Data.Colour.Names as C
import qualified Data.Colour.SRGB as C
import GHC.Real
import Graphics.Rendering.Plot.Light.Internal.Geometry
svgHeader :: Frame Int -> Svg -> Svg
svgHeader fd =
S.docTypeSvg
! SA.version "1.1"
! SA.width (vi $ width fd)
! SA.height (vi $ height fd)
! SA.viewbox (vis [xmin fd, ymin fd, xmax fd, ymax fd])
rectCentered :: (Show a, RealFrac a) =>
Point a
-> a
-> a
-> Maybe (C.Colour Double)
-> Maybe (C.Colour Double)
-> Svg
rectCentered (Point x0 y0) wid hei scol fcol = S.g ! SA.transform (S.translate x0c y0c) $
S.rect ! SA.width (vd wid) ! SA.height (vd hei) ! colourFillOpt fcol ! colourStrokeOpt scol where
x0c = x0 (wid / 2)
y0c = y0 (hei / 2)
line :: (Show a, RealFrac a) =>
Point a
-> Point a
-> a
-> LineStroke_ a
-> C.Colour Double
-> Svg
line (Point x1 y1) (Point x2 y2) sw Continuous col = S.line ! SA.x1 (vd x1) ! SA.y1 (vd y1) ! SA.x2 (vd x2) ! SA.y2 (vd y2) ! SA.stroke (colourAttr col ) ! SA.strokeWidth (vd sw)
line (Point x1 y1) (Point x2 y2) sw (Dashed d) col = S.line ! SA.x1 (vd x1) ! SA.y1 (vd y1) ! SA.x2 (vd x2) ! SA.y2 (vd y2) ! SA.stroke (colourAttr col ) ! SA.strokeWidth (vd sw) ! strokeDashArray d
strokeDashArray :: Real a => [a] -> S.Attribute
strokeDashArray sz = SA.strokeDasharray (S.toValue str) where
str = intercalate ", " $ map (show . real) sz
data LineStroke_ a = Continuous | Dashed [a] deriving (Eq, Show)
tick :: (Show a, RealFrac a) => Axis -> a -> a -> C.Colour Double -> LineStroke_ a -> Point a -> Svg
tick ax len sw col ls (Point x y) = line (Point x1 y1) (Point x2 y2) sw ls col where
lh = len / 2
(x1, y1, x2, y2)
| ax == Y = (x, ylh, x, y+lh)
| otherwise = (xlh, y, x+lh, y)
tickX, tickY :: (Show a, RealFrac a) =>
a
-> a
-> C.Colour Double
-> LineStroke_ a
-> Point a
-> Svg
tickX = tick X
tickY = tick Y
ticks :: (Foldable t, Show a, RealFrac a) =>
Axis
-> a
-> a
-> C.Colour Double
-> LineStroke_ a
-> t (Point a)
-> Svg
ticks ax len sw col ls ps = forM_ ps (tick ax len sw col ls)
axis :: (Functor t, Foldable t, Show a, RealFrac a) =>
Axis
-> a
-> a
-> C.Colour Double
-> a
-> Point a
-> LineStroke_ a
-> t (Point a)
-> Svg
axis ax len sw col tickLenFrac p@(Point x y) ls ps = do
tick ax len sw col ls p
ticks (otherAxis ax) (tickLenFrac * len) sw col ls (f <$> ps)
where
f | ax == X = setPointY y
| otherwise = setPointX x
text :: (Show a, Real a) =>
a
-> C.Colour Double
-> TextAnchor_
-> T.Text
-> V2 a
-> Point a
-> Svg
text rot col ta te (V2 vx vy) (Point x y) = S.text_ (S.toMarkup te) ! SA.x (vd vx) ! SA.y (vd vy) ! SA.transform (S.translate (real x) (real y) <> S.rotate (real rot)) ! SA.fill (colourAttr col) ! textAnchor ta
data TextAnchor_ = TAStart | TAMiddle | TAEnd deriving (Eq, Show)
textAnchor :: TextAnchor_ -> S.Attribute
textAnchor TAStart = SA.textAnchor (vs "start")
textAnchor TAMiddle = SA.textAnchor (vs "middle")
textAnchor TAEnd = SA.textAnchor (vs "end")
circle
:: (Real a1, Real a) =>
Point a1
-> a
-> Maybe (C.Colour Double)
-> Maybe (C.Colour Double)
-> Svg
circle (Point x y) r scol fcol =
S.circle ! SA.cx (vd x) ! SA.cy (vd y) ! SA.r (vd r) ! colourFillOpt fcol ! colourStrokeOpt scol
polyline :: (Foldable t, Show a1, Show a, RealFrac a, RealFrac a1) =>
t (Point a)
-> a1
-> LineStroke_ a
-> StrokeLineJoin_
-> C.Colour Double
-> Svg
polyline lis sw Continuous slj col = S.polyline ! SA.points (S.toValue $ unwords $ map show $ F.toList lis) ! SA.fill none ! SA.stroke (colourAttr col ) ! SA.strokeWidth (vd sw) ! strokeLineJoin slj
polyline lis sw (Dashed d) slj col = S.polyline ! SA.points (S.toValue $ unwords $ map show $ F.toList lis) ! SA.fill none ! SA.stroke (colourAttr col ) ! SA.strokeWidth (vd sw) ! strokeLineJoin slj ! strokeDashArray d
none :: S.AttributeValue
none = S.toValue ("none" :: String)
colourFillOpt :: Maybe (C.Colour Double) -> S.Attribute
colourFillOpt Nothing = SA.fill none
colourFillOpt (Just c) = SA.fill (colourAttr c)
colourStrokeOpt :: Maybe (C.Colour Double) -> S.Attribute
colourStrokeOpt Nothing = SA.stroke none
colourStrokeOpt (Just c) = SA.stroke (colourAttr c)
data StrokeLineJoin_ = Miter | Round | Bevel | Inherit deriving (Eq, Show)
strokeLineJoin :: StrokeLineJoin_ -> S.Attribute
strokeLineJoin slj = SA.strokeLinejoin (S.toValue str) where
str | slj == Miter = "miter" :: String
| slj == Round = "round"
| slj == Bevel = "bevel"
| otherwise = "inherit"
colourAttr :: C.Colour Double -> S.AttributeValue
colourAttr = S.toValue . C.sRGB24show
vs :: String -> S.AttributeValue
vs x = S.toValue (x :: String)
vi :: Int -> S.AttributeValue
vi = S.toValue
vis :: [Int] -> S.AttributeValue
vis = S.toValue . unwords . map show
vd0 :: Double -> S.AttributeValue
vd0 = S.toValue
vd :: Real a => a -> S.AttributeValue
vd = vd0 . real
real :: (Real a, Fractional b) => a -> b
real = fromRational . toRational
showd :: Real a => a -> String
showd = show . real