{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RebindableSyntax #-}
{-# LANGUAGE NegativeLiterals #-}
{-# OPTIONS_GHC -Wall #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# OPTIONS_GHC -fno-warn-type-defaults #-}

-- | Examples of chart construction.
module Chart.Examples
  ( unitExample,
    svgOptionsExample,
    hudOptionsExample,
    rectExample,
    textExample,
    glyphsExample,
    lineExample,
    barDataExample,
    barExample,
    waveExample,
    lglyphExample,
    glinesExample,
    compoundExample,
    textLocalExample,
    labelExample,
    legendExample,
    surfaceExample,
    rosenbrock,
    arcExample,
    arcFlagsExample,
    ellipseExample,
    quadExample,
    cubicExample,
    pathExample,
    vennExample,
    arrowExample,
    writeAllExamples,
  )
where

import Chart
import Control.Lens
import qualified Data.List as List
import qualified Data.Text as Text
import NumHask.Prelude hiding (lines)

-- | unit example
--
-- ![unit example](other/unit.svg)
unitExample :: ChartSvg
unitExample :: ChartSvg
unitExample = ChartSvg
forall a. Monoid a => a
mempty ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
& ([Chart Double] -> Identity [Chart Double])
-> ChartSvg -> Identity ChartSvg
forall a. IsLabel "chartList" a => a
forall (x :: Symbol) a. IsLabel x a => a
#chartList (([Chart Double] -> Identity [Chart Double])
 -> ChartSvg -> Identity ChartSvg)
-> [Chart Double] -> ChartSvg -> ChartSvg
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (RectStyle -> Annotation
RectA RectStyle
defaultRectStyle) [XY Double
forall a. Multiplicative a => a
one]]

-- | 'HudOptions' example
--
-- ![hudoptions example](other/hudoptions.svg)
hudOptionsExample :: ChartSvg
hudOptionsExample :: ChartSvg
hudOptionsExample =
  ChartSvg
forall a. Monoid a => a
mempty
    ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
& (HudOptions -> Identity HudOptions)
-> ChartSvg -> Identity ChartSvg
forall a. IsLabel "hudOptions" a => a
forall (x :: Symbol) a. IsLabel x a => a
#hudOptions ((HudOptions -> Identity HudOptions)
 -> ChartSvg -> Identity ChartSvg)
-> HudOptions -> ChartSvg -> ChartSvg
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Colour -> HudOptions -> HudOptions
colourHudOptions Colour
dark HudOptions
defaultHudOptions
    ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
& ([Chart Double] -> Identity [Chart Double])
-> ChartSvg -> Identity ChartSvg
forall a. IsLabel "chartList" a => a
forall (x :: Symbol) a. IsLabel x a => a
#chartList (([Chart Double] -> Identity [Chart Double])
 -> ChartSvg -> Identity ChartSvg)
-> [Chart Double] -> ChartSvg -> ChartSvg
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart Annotation
BlankA [XY Double
forall a. Multiplicative a => a
one]]

-- | 'SvgOptions' example.
--
-- ![svgoptions example](other/svgoptions.svg)
svgOptionsExample :: ChartSvg
svgOptionsExample :: ChartSvg
svgOptionsExample =
  ChartSvg
forall a. Monoid a => a
mempty
    ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
& (SvgOptions -> Identity SvgOptions)
-> ChartSvg -> Identity ChartSvg
forall a. IsLabel "svgOptions" a => a
forall (x :: Symbol) a. IsLabel x a => a
#svgOptions ((SvgOptions -> Identity SvgOptions)
 -> ChartSvg -> Identity ChartSvg)
-> (SvgOptions -> SvgOptions) -> ChartSvg -> ChartSvg
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (ChartAspect -> Identity ChartAspect)
-> SvgOptions -> Identity SvgOptions
forall a. IsLabel "chartAspect" a => a
forall (x :: Symbol) a. IsLabel x a => a
#chartAspect ((ChartAspect -> Identity ChartAspect)
 -> SvgOptions -> Identity SvgOptions)
-> ChartAspect -> SvgOptions -> SvgOptions
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double -> ChartAspect
FixedAspect Double
0.7
    ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
& ([Chart Double] -> Identity [Chart Double])
-> ChartSvg -> Identity ChartSvg
forall a. IsLabel "chartList" a => a
forall (x :: Symbol) a. IsLabel x a => a
#chartList (([Chart Double] -> Identity [Chart Double])
 -> ChartSvg -> Identity ChartSvg)
-> [Chart Double] -> ChartSvg -> ChartSvg
forall s t a b. ASetter s t a b -> b -> s -> t
.~ (LineStyle -> [Point Double] -> Chart Double)
-> [LineStyle] -> [[Point Double]] -> [Chart Double]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\LineStyle
s [Point Double]
d -> Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (LineStyle -> Annotation
LineA LineStyle
s) ((Point Double -> XY Double) -> [Point Double] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Point Double -> XY Double
forall a. Point a -> XY a
PointXY [Point Double]
d)) [LineStyle]
lopts [[Point Double]]
ls

-- | rect example
--
-- ![rect example](other/rect.svg)
rectExample :: ChartSvg
rectExample :: ChartSvg
rectExample =
  ChartSvg
forall a. Monoid a => a
mempty
    ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
& (HudOptions -> Identity HudOptions)
-> ChartSvg -> Identity ChartSvg
forall a. IsLabel "hudOptions" a => a
forall (x :: Symbol) a. IsLabel x a => a
#hudOptions ((HudOptions -> Identity HudOptions)
 -> ChartSvg -> Identity ChartSvg)
-> HudOptions -> ChartSvg -> ChartSvg
forall s t a b. ASetter s t a b -> b -> s -> t
.~ (HudOptions
defaultHudOptions HudOptions -> (HudOptions -> HudOptions) -> HudOptions
forall a b. a -> (a -> b) -> b
& ([AxisOptions] -> Identity [AxisOptions])
-> HudOptions -> Identity HudOptions
forall a. IsLabel "hudAxes" a => a
forall (x :: Symbol) a. IsLabel x a => a
#hudAxes (([AxisOptions] -> Identity [AxisOptions])
 -> HudOptions -> Identity HudOptions)
-> [AxisOptions] -> HudOptions -> HudOptions
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [AxisOptions
defaultAxisOptions])
    ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
& ([Chart Double] -> Identity [Chart Double])
-> ChartSvg -> Identity ChartSvg
forall a. IsLabel "chartList" a => a
forall (x :: Symbol) a. IsLabel x a => a
#chartList (([Chart Double] -> Identity [Chart Double])
 -> ChartSvg -> Identity ChartSvg)
-> [Chart Double] -> ChartSvg -> ChartSvg
forall s t a b. ASetter s t a b -> b -> s -> t
.~ (Annotation -> [XY Double] -> Chart Double)
-> [Annotation] -> [[XY Double]] -> [Chart Double]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (RectStyle -> Annotation
RectA (RectStyle -> Annotation) -> [RectStyle] -> [Annotation]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [RectStyle]
ropts) ((Rect Double -> XY Double) -> [Rect Double] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Rect Double -> XY Double
forall a. Rect a -> XY a
RectXY ([Rect Double] -> [XY Double]) -> [[Rect Double]] -> [[XY Double]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [[Rect Double]]
rss)

rss :: [[Rect Double]]
rss :: [[Rect Double]]
rss =
  [ (Double -> Double) -> Range Double -> Int -> [Rect Double]
forall a.
(Field a, FromIntegral a Int, Ord a) =>
(a -> a) -> Range a -> Int -> [Rect a]
gridR (\Double
x -> Double -> Double
forall a. ExpField a => a -> a
exp (- (Double
x Double -> Double -> Double
forall a. ExpField a => a -> a -> a
** Double
2) Double -> Double -> Double
forall a. Divisive a => a -> a -> a
/ Double
2)) (Double -> Double -> Range Double
forall a. a -> a -> Range a
Range Double
-5 Double
5) Int
50,
    (Double -> Double) -> Range Double -> Int -> [Rect Double]
forall a.
(Field a, FromIntegral a Int, Ord a) =>
(a -> a) -> Range a -> Int -> [Rect a]
gridR (\Double
x -> Double
0.5 Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double -> Double
forall a. ExpField a => a -> a
exp (- (Double
x Double -> Double -> Double
forall a. ExpField a => a -> a -> a
** Double
2) Double -> Double -> Double
forall a. Divisive a => a -> a -> a
/ Double
8)) (Double -> Double -> Range Double
forall a. a -> a -> Range a
Range Double
-5 Double
5) Int
50
  ]

ropts :: [RectStyle]
ropts :: [RectStyle]
ropts =
  [ Colour -> RectStyle
blob ([Colour]
palette1 [Colour] -> Int -> Colour
forall a. [a] -> Int -> a
List.!! Int
1),
    Colour -> RectStyle
blob ([Colour]
palette1 [Colour] -> Int -> Colour
forall a. [a] -> Int -> a
List.!! Int
2)
  ]

-- | line example
--
-- Example in cabal file
--
-- This 'lineExample' provides a bit more detail for testing huds.
--
-- Simplified example:
--
-- >>> :set -XOverloadedLabels
-- >>> import Chart
-- >>> let xs = fmap (fmap (uncurry Point)) [[(0.0, 1.0), (1.0, 1.0), (2.0, 5.0)], [(0.0, 0.0), (3.2, 3.0)], [(0.5, 4.0), (0.5, 0)]] :: [[Point Double]]
-- >>> xs
-- [[Point 0.0 1.0,Point 1.0 1.0,Point 2.0 5.0],[Point 0.0 0.0,Point 3.2 3.0],[Point 0.5 4.0,Point 0.5 0.0]]
--
-- >>> let anns = zipWith (\w c -> LineA (defaultLineStyle & #width .~ w & #color .~ c)) [0.015, 0.03, 0.01] palette1
-- >>> anns
-- [LineA (LineStyle {width = 1.5e-2, color = Colour 0.69 0.35 0.16 1.00, linecap = Nothing, linejoin = Nothing, dasharray = Nothing, dashoffset = Nothing}),LineA (LineStyle {width = 3.0e-2, color = Colour 0.65 0.81 0.89 1.00, linecap = Nothing, linejoin = Nothing, dasharray = Nothing, dashoffset = Nothing}),LineA (LineStyle {width = 1.0e-2, color = Colour 0.12 0.47 0.71 1.00, linecap = Nothing, linejoin = Nothing, dasharray = Nothing, dashoffset = Nothing})]
--
-- >>> let lineExample = mempty & (#chartList .~ zipWith Chart anns (fmap (fmap PointXY) xs)) & #hudOptions .~ defaultHudOptions & #svgOptions .~ defaultSvgOptions :: ChartSvg
-- >>> :t lineExample
-- lineExample :: ChartSvg
--
-- > writeChartSvg "other/line.svg" lineExample
--
-- ![line example](other/line.svg)
lineExample :: ChartSvg
lineExample :: ChartSvg
lineExample =
  ChartSvg
forall a. Monoid a => a
mempty
    ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
& (SvgOptions -> Identity SvgOptions)
-> ChartSvg -> Identity ChartSvg
forall a. IsLabel "svgOptions" a => a
forall (x :: Symbol) a. IsLabel x a => a
#svgOptions ((SvgOptions -> Identity SvgOptions)
 -> ChartSvg -> Identity ChartSvg)
-> ((ChartAspect -> Identity ChartAspect)
    -> SvgOptions -> Identity SvgOptions)
-> (ChartAspect -> Identity ChartAspect)
-> ChartSvg
-> Identity ChartSvg
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (ChartAspect -> Identity ChartAspect)
-> SvgOptions -> Identity SvgOptions
forall a. IsLabel "chartAspect" a => a
forall (x :: Symbol) a. IsLabel x a => a
#chartAspect ((ChartAspect -> Identity ChartAspect)
 -> ChartSvg -> Identity ChartSvg)
-> ChartAspect -> ChartSvg -> ChartSvg
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double -> ChartAspect
CanvasAspect Double
1.5
    ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
& (HudOptions -> Identity HudOptions)
-> ChartSvg -> Identity ChartSvg
forall a. IsLabel "hudOptions" a => a
forall (x :: Symbol) a. IsLabel x a => a
#hudOptions
    ((HudOptions -> Identity HudOptions)
 -> ChartSvg -> Identity ChartSvg)
-> HudOptions -> ChartSvg -> ChartSvg
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Text
-> Maybe Text
-> Maybe (LegendOptions, [(Annotation, Text)])
-> HudOptions
exampleLineHudOptions
           Text
"Line Chart"
           (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"An example from chart-svg")
           ((LegendOptions, [(Annotation, Text)])
-> Maybe (LegendOptions, [(Annotation, Text)])
forall a. a -> Maybe a
Just (LegendOptions
defaultLegendOptions, [Annotation] -> [Text] -> [(Annotation, Text)]
forall a b. [a] -> [b] -> [(a, b)]
zip (LineStyle -> Annotation
LineA (LineStyle -> Annotation) -> [LineStyle] -> [Annotation]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [LineStyle]
lopts) [Text
"hockey", Text
"line", Text
"vertical"]))
    ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
& ([Chart Double] -> Identity [Chart Double])
-> ChartSvg -> Identity ChartSvg
forall a. IsLabel "chartList" a => a
forall (x :: Symbol) a. IsLabel x a => a
#chartList
    (([Chart Double] -> Identity [Chart Double])
 -> ChartSvg -> Identity ChartSvg)
-> [Chart Double] -> ChartSvg -> ChartSvg
forall s t a b. ASetter s t a b -> b -> s -> t
.~ (LineStyle -> [Point Double] -> Chart Double)
-> [LineStyle] -> [[Point Double]] -> [Chart Double]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\LineStyle
s [Point Double]
d -> Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (LineStyle -> Annotation
LineA LineStyle
s) ((Point Double -> XY Double) -> [Point Double] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Point Double -> XY Double
forall a. Point a -> XY a
PointXY [Point Double]
d)) [LineStyle]
lopts [[Point Double]]
ls

ls :: [[Point Double]]
ls :: [[Point Double]]
ls =
  ((Double, Double) -> Point Double)
-> [(Double, Double)] -> [Point Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Double -> Double -> Point Double)
-> (Double, Double) -> Point Double
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Double -> Double -> Point Double
forall a. a -> a -> Point a
Point)
    ([(Double, Double)] -> [Point Double])
-> [[(Double, Double)]] -> [[Point Double]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ [(Double
0.0, Double
1.0), (Double
1.0, Double
1.0), (Double
2.0, Double
5.0)],
          [(Double
0.0, Double
0.0), (Double
2.8, Double
3.0)],
          [(Double
0.5, Double
4.0), (Double
0.5, Double
0)]
        ]

lopts :: [LineStyle]
lopts :: [LineStyle]
lopts =
  [ LineStyle
defaultLineStyle LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> LineStyle -> Identity LineStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> LineStyle -> Identity LineStyle)
-> Colour -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ([Colour]
palette1 [Colour] -> Int -> Colour
forall a. [a] -> Int -> a
List.!! Int
0) LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> LineStyle -> Identity LineStyle
forall a. IsLabel "width" a => a
forall (x :: Symbol) a. IsLabel x a => a
#width ((Double -> Identity Double) -> LineStyle -> Identity LineStyle)
-> Double -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.015,
    LineStyle
defaultLineStyle LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> LineStyle -> Identity LineStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> LineStyle -> Identity LineStyle)
-> Colour -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ([Colour]
palette1 [Colour] -> Int -> Colour
forall a. [a] -> Int -> a
List.!! Int
1) LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> LineStyle -> Identity LineStyle
forall a. IsLabel "width" a => a
forall (x :: Symbol) a. IsLabel x a => a
#width ((Double -> Identity Double) -> LineStyle -> Identity LineStyle)
-> Double -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.03,
    LineStyle
defaultLineStyle LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> LineStyle -> Identity LineStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> LineStyle -> Identity LineStyle)
-> Colour -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ([Colour]
palette1 [Colour] -> Int -> Colour
forall a. [a] -> Int -> a
List.!! Int
2) LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> LineStyle -> Identity LineStyle
forall a. IsLabel "width" a => a
forall (x :: Symbol) a. IsLabel x a => a
#width ((Double -> Identity Double) -> LineStyle -> Identity LineStyle)
-> Double -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.01
  ]

exampleLineHudOptions :: Text -> Maybe Text -> Maybe (LegendOptions, [(Annotation, Text)]) -> HudOptions
exampleLineHudOptions :: Text
-> Maybe Text
-> Maybe (LegendOptions, [(Annotation, Text)])
-> HudOptions
exampleLineHudOptions Text
t1 Maybe Text
t2 Maybe (LegendOptions, [(Annotation, Text)])
legends' =
  HudOptions
defaultHudOptions
    HudOptions -> (HudOptions -> HudOptions) -> HudOptions
forall a b. a -> (a -> b) -> b
& ([Title] -> Identity [Title]) -> HudOptions -> Identity HudOptions
forall a. IsLabel "hudTitles" a => a
forall (x :: Symbol) a. IsLabel x a => a
#hudTitles
      (([Title] -> Identity [Title])
 -> HudOptions -> Identity HudOptions)
-> [Title] -> HudOptions -> HudOptions
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ( [ Text -> Title
defaultTitle Text
t1
               Title -> (Title -> Title) -> Title
forall a b. a -> (a -> b) -> b
& (TextStyle -> Identity TextStyle) -> Title -> Identity Title
forall a. IsLabel "style" a => a
forall (x :: Symbol) a. IsLabel x a => a
#style ((TextStyle -> Identity TextStyle) -> Title -> Identity Title)
-> ((Double -> Identity Double) -> TextStyle -> Identity TextStyle)
-> (Double -> Identity Double)
-> Title
-> Identity Title
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Double -> Identity Double) -> TextStyle -> Identity TextStyle
forall a. IsLabel "size" a => a
forall (x :: Symbol) a. IsLabel x a => a
#size ((Double -> Identity Double) -> Title -> Identity Title)
-> Double -> Title -> Title
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.08
           ]
             [Title] -> [Title] -> [Title]
forall a. Semigroup a => a -> a -> a
<> [Title] -> (Text -> [Title]) -> Maybe Text -> [Title]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
               []
               ( \Text
x ->
                   [ Text -> Title
defaultTitle Text
x
                       Title -> (Title -> Title) -> Title
forall a b. a -> (a -> b) -> b
& (TextStyle -> Identity TextStyle) -> Title -> Identity Title
forall a. IsLabel "style" a => a
forall (x :: Symbol) a. IsLabel x a => a
#style ((TextStyle -> Identity TextStyle) -> Title -> Identity Title)
-> ((Double -> Identity Double) -> TextStyle -> Identity TextStyle)
-> (Double -> Identity Double)
-> Title
-> Identity Title
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Double -> Identity Double) -> TextStyle -> Identity TextStyle
forall a. IsLabel "size" a => a
forall (x :: Symbol) a. IsLabel x a => a
#size ((Double -> Identity Double) -> Title -> Identity Title)
-> Double -> Title -> Title
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.05
                       Title -> (Title -> Title) -> Title
forall a b. a -> (a -> b) -> b
& (Place -> Identity Place) -> Title -> Identity Title
forall a. IsLabel "place" a => a
forall (x :: Symbol) a. IsLabel x a => a
#place ((Place -> Identity Place) -> Title -> Identity Title)
-> Place -> Title -> Title
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Place
PlaceBottom
                       Title -> (Title -> Title) -> Title
forall a b. a -> (a -> b) -> b
& (Anchor -> Identity Anchor) -> Title -> Identity Title
forall a. IsLabel "anchor" a => a
forall (x :: Symbol) a. IsLabel x a => a
#anchor ((Anchor -> Identity Anchor) -> Title -> Identity Title)
-> Anchor -> Title -> Title
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Anchor
AnchorEnd
                   ]
               )
               Maybe Text
t2
         )
    HudOptions -> (HudOptions -> HudOptions) -> HudOptions
forall a b. a -> (a -> b) -> b
& (Maybe (LegendOptions, [(Annotation, Text)])
 -> Identity (Maybe (LegendOptions, [(Annotation, Text)])))
-> HudOptions -> Identity HudOptions
forall a. IsLabel "hudLegend" a => a
forall (x :: Symbol) a. IsLabel x a => a
#hudLegend ((Maybe (LegendOptions, [(Annotation, Text)])
  -> Identity (Maybe (LegendOptions, [(Annotation, Text)])))
 -> HudOptions -> Identity HudOptions)
-> Maybe (LegendOptions, [(Annotation, Text)])
-> HudOptions
-> HudOptions
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Maybe (LegendOptions, [(Annotation, Text)])
legends'
    HudOptions -> (HudOptions -> HudOptions) -> HudOptions
forall a b. a -> (a -> b) -> b
& ([AxisOptions] -> Identity [AxisOptions])
-> HudOptions -> Identity HudOptions
forall a. IsLabel "hudAxes" a => a
forall (x :: Symbol) a. IsLabel x a => a
#hudAxes (([AxisOptions] -> Identity [AxisOptions])
 -> HudOptions -> Identity HudOptions)
-> ([AxisOptions] -> [AxisOptions]) -> HudOptions -> HudOptions
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (AxisOptions -> AxisOptions) -> [AxisOptions] -> [AxisOptions]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Tick -> Identity Tick) -> AxisOptions -> Identity AxisOptions
forall a. IsLabel "axisTick" a => a
forall (x :: Symbol) a. IsLabel x a => a
#axisTick ((Tick -> Identity Tick) -> AxisOptions -> Identity AxisOptions)
-> ((TickStyle -> Identity TickStyle) -> Tick -> Identity Tick)
-> (TickStyle -> Identity TickStyle)
-> AxisOptions
-> Identity AxisOptions
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (TickStyle -> Identity TickStyle) -> Tick -> Identity Tick
forall a. IsLabel "tstyle" a => a
forall (x :: Symbol) a. IsLabel x a => a
#tstyle ((TickStyle -> Identity TickStyle)
 -> AxisOptions -> Identity AxisOptions)
-> TickStyle -> AxisOptions -> AxisOptions
forall s t a b. ASetter s t a b -> b -> s -> t
.~ FormatN -> Int -> TickExtend -> TickStyle
TickRound (Maybe Int -> FormatN
FormatFixed (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
1)) Int
8 TickExtend
TickExtend)

-- | text example
--
-- ![text example](other/text.svg)
textExample :: ChartSvg
textExample :: ChartSvg
textExample =
  ChartSvg
forall a. Monoid a => a
mempty ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
& ([Chart Double] -> Identity [Chart Double])
-> ChartSvg -> Identity ChartSvg
forall a. IsLabel "chartList" a => a
forall (x :: Symbol) a. IsLabel x a => a
#chartList
    (([Chart Double] -> Identity [Chart Double])
 -> ChartSvg -> Identity ChartSvg)
-> [Chart Double] -> ChartSvg -> ChartSvg
forall s t a b. ASetter s t a b -> b -> s -> t
.~ (Annotation -> [XY Double] -> Chart Double)
-> [Annotation] -> [[XY Double]] -> [Chart Double]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith
      Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart 
      (TextStyle -> [Text] -> Annotation
TextA (TextStyle
defaultTextStyle TextStyle -> (TextStyle -> TextStyle) -> TextStyle
forall a b. a -> (a -> b) -> b
& ((Colour -> Identity Colour) -> TextStyle -> Identity TextStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> TextStyle -> Identity TextStyle)
-> Colour -> TextStyle -> TextStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Colour
dark) TextStyle -> (TextStyle -> TextStyle) -> TextStyle
forall a b. a -> (a -> b) -> b
& ((Double -> Identity Double) -> TextStyle -> Identity TextStyle
forall a. IsLabel "size" a => a
forall (x :: Symbol) a. IsLabel x a => a
#size ((Double -> Identity Double) -> TextStyle -> Identity TextStyle)
-> Double -> TextStyle -> TextStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ (Double
0.05 :: Double))) ([Text] -> Annotation)
-> ((Text, Point Double) -> [Text])
-> (Text, Point Double)
-> Annotation
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: []) (Text -> [Text])
-> ((Text, Point Double) -> Text) -> (Text, Point Double) -> [Text]
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Text, Point Double) -> Text
forall a b. (a, b) -> a
fst ((Text, Point Double) -> Annotation)
-> [(Text, Point Double)] -> [Annotation]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Text, Point Double)]
ts)
      ((XY Double -> [XY Double] -> [XY Double]
forall a. a -> [a] -> [a]
: []) (XY Double -> [XY Double])
-> ((Text, Point Double) -> XY Double)
-> (Text, Point Double)
-> [XY Double]
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Point Double -> XY Double
forall a. Point a -> XY a
PointXY (Point Double -> XY Double)
-> ((Text, Point Double) -> Point Double)
-> (Text, Point Double)
-> XY Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Text, Point Double) -> Point Double
forall a b. (a, b) -> b
snd ((Text, Point Double) -> [XY Double])
-> [(Text, Point Double)] -> [[XY Double]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Text, Point Double)]
ts)
  where
    ts :: [(Text, Point Double)]
    ts :: [(Text, Point Double)]
ts =
      [Text] -> [Point Double] -> [(Text, Point Double)]
forall a b. [a] -> [b] -> [(a, b)]
zip
        ((Char -> Text) -> [Char] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Char -> Text
Text.singleton [Char
'a' .. Char
'y'])
        [Double -> Double -> Point Double
forall a. a -> a -> Point a
Point (Double -> Double
forall a. TrigField a => a -> a
sin (Double
x Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double
0.1)) Double
x | Double
x <- [Double
0 .. Double
25]]

-- | glyphs example
--
-- ![glyphs example](other/glyphs.svg)
glyphsExample :: ChartSvg
glyphsExample :: ChartSvg
glyphsExample =
  ChartSvg
forall a. Monoid a => a
mempty ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
&
  #svgOptions . #svgHeight .~ 50 &
  #chartList
    .~ zipWith
      ( \(sh, bs) p ->
          Chart
            ( GlyphA
                ( defaultGlyphStyle
                    & #size .~ (0.1 :: Double)
                    & #borderSize .~ bs
                    & #shape .~ sh
                )
            )
            [p]
      )
      [ (CircleGlyph, 0.01 :: Double),
        (SquareGlyph, 0.01),
        (RectSharpGlyph 0.75, 0.01),
        (RectRoundedGlyph 0.75 0.01 0.01, 0.01),
        (EllipseGlyph 0.75, 0),
        (VLineGlyph 0.005, 0.01),
        (HLineGlyph 0.005, 0.01),
        (TriangleGlyph (Point 0.0 0.0) (Point 1 1) (Point 1 0), 0.01),
        (PathGlyph "M0.05,-0.03660254037844387 A0.1 0.1 0.0 0 1 0.0,0.05 0.1 0.1 0.0 0 1 -0.05,-0.03660254037844387 0.1 0.1 0.0 0 1 0.05,-0.03660254037844387 Z", 0.01)
      ]
      [P x 0 | x <- [0 .. (8 :: Double)]]

-- | Example data for Bar chart
barDataExample :: BarData
barDataExample :: BarData
barDataExample =
  [[Double]] -> Maybe [Text] -> Maybe [Text] -> BarData
BarData
    [[Double
1, Double
2, Double
3, Double
5, Double
8, Double
0, Double
-2, Double
11, Double
2, Double
1], [Double
1 .. Double
10]]
    ([Text] -> Maybe [Text]
forall a. a -> Maybe a
Just ((Text
"row " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) (Text -> Text) -> (Int -> Text) -> Int -> Text
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. [Char] -> Text
pack ([Char] -> Text) -> (Int -> [Char]) -> Int -> Text
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> [Char]
forall a b. (Show a, ConvertText [Char] b) => a -> b
show (Int -> Text) -> [Int] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([Int
1 .. Int
11]::[Int])))
    ([Text] -> Maybe [Text]
forall a. a -> Maybe a
Just ((Text
"column " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) (Text -> Text) -> (Int -> Text) -> Int -> Text
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. [Char] -> Text
pack ([Char] -> Text) -> (Int -> [Char]) -> Int -> Text
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int -> [Char]
forall a b. (Show a, ConvertText [Char] b) => a -> b
show (Int -> Text) -> [Int] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([Int
1 .. Int
2]::[Int])))

-- | Bar chart example.
--
-- ![bar example](other/bar.svg)
barExample :: ChartSvg
barExample :: ChartSvg
barExample = ChartSvg
forall a. Monoid a => a
mempty ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
& (HudOptions -> Identity HudOptions)
-> ChartSvg -> Identity ChartSvg
forall a. IsLabel "hudOptions" a => a
forall (x :: Symbol) a. IsLabel x a => a
#hudOptions ((HudOptions -> Identity HudOptions)
 -> ChartSvg -> Identity ChartSvg)
-> HudOptions -> ChartSvg -> ChartSvg
forall s t a b. ASetter s t a b -> b -> s -> t
.~ HudOptions
hc ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
& ([Chart Double] -> Identity [Chart Double])
-> ChartSvg -> Identity ChartSvg
forall a. IsLabel "chartList" a => a
forall (x :: Symbol) a. IsLabel x a => a
#chartList (([Chart Double] -> Identity [Chart Double])
 -> ChartSvg -> Identity ChartSvg)
-> [Chart Double] -> ChartSvg -> ChartSvg
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [Chart Double]
cs
  where
    (HudOptions
hc, [Chart Double]
cs) = BarOptions -> BarData -> (HudOptions, [Chart Double])
barChart BarOptions
defaultBarOptions BarData
barDataExample

-- | A reminder that Text scale is at representation level, and so doesn't scale compared with other chart elements, such as a rectangle.
--
-- ![text local example](other/textlocal.svg) 
textLocalExample :: ChartSvg
textLocalExample :: ChartSvg
textLocalExample =
  ChartSvg
forall a. Monoid a => a
mempty ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
& ([Chart Double] -> Identity [Chart Double])
-> ChartSvg -> Identity ChartSvg
forall a. IsLabel "chartList" a => a
forall (x :: Symbol) a. IsLabel x a => a
#chartList
    (([Chart Double] -> Identity [Chart Double])
 -> ChartSvg -> Identity ChartSvg)
-> [Chart Double] -> ChartSvg -> ChartSvg
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [ Chart Double
t1,
         Chart Double
t2,
         Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (RectStyle -> Annotation
RectA RectStyle
rs) [Rect Double -> XY Double
forall a. Rect a -> XY a
RectXY (Maybe (Rect Double) -> Rect Double
padBox (Maybe (Rect Double) -> Rect Double)
-> Maybe (Rect Double) -> Rect Double
forall a b. (a -> b) -> a -> b
$ Chart Double -> Maybe (Rect Double)
styleBox Chart Double
t1)],
         Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (RectStyle -> Annotation
RectA RectStyle
rs) [Rect Double -> XY Double
forall a. Rect a -> XY a
RectXY (Maybe (Rect Double) -> Rect Double
padBox (Maybe (Rect Double) -> Rect Double)
-> Maybe (Rect Double) -> Rect Double
forall a b. (a -> b) -> a -> b
$ Chart Double -> Maybe (Rect Double)
styleBox Chart Double
t2)]
       ]
  where
    rs :: RectStyle
rs = RectStyle
defaultRectStyle RectStyle -> (RectStyle -> RectStyle) -> RectStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> RectStyle -> Identity RectStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> RectStyle -> Identity RectStyle)
-> (Colour -> Colour) -> RectStyle -> RectStyle
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ Double -> Colour -> Colour
setOpac Double
0.1
    t1 :: Chart Double
t1 =
      Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart
        ( TextStyle -> [Text] -> Annotation
TextA
            (TextStyle
defaultTextStyle TextStyle -> (TextStyle -> TextStyle) -> TextStyle
forall a b. a -> (a -> b) -> b
& (Anchor -> Identity Anchor) -> TextStyle -> Identity TextStyle
forall a. IsLabel "anchor" a => a
forall (x :: Symbol) a. IsLabel x a => a
#anchor ((Anchor -> Identity Anchor) -> TextStyle -> Identity TextStyle)
-> Anchor -> TextStyle -> TextStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Anchor
AnchorStart TextStyle -> (TextStyle -> TextStyle) -> TextStyle
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> TextStyle -> Identity TextStyle
forall a. IsLabel "hsize" a => a
forall (x :: Symbol) a. IsLabel x a => a
#hsize ((Double -> Identity Double) -> TextStyle -> Identity TextStyle)
-> Double -> TextStyle -> TextStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.5 TextStyle -> (TextStyle -> TextStyle) -> TextStyle
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> TextStyle -> Identity TextStyle
forall a. IsLabel "size" a => a
forall (x :: Symbol) a. IsLabel x a => a
#size ((Double -> Identity Double) -> TextStyle -> Identity TextStyle)
-> Double -> TextStyle -> TextStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.08)
            [Text
"a pretty long piece of text"]
        )
        [XY Double
forall a. Additive a => a
zero]
    t2 :: Chart Double
t2 =
      Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart
        ( TextStyle -> [Text] -> Annotation
TextA
            (TextStyle
defaultTextStyle TextStyle -> (TextStyle -> TextStyle) -> TextStyle
forall a b. a -> (a -> b) -> b
& (Anchor -> Identity Anchor) -> TextStyle -> Identity TextStyle
forall a. IsLabel "anchor" a => a
forall (x :: Symbol) a. IsLabel x a => a
#anchor ((Anchor -> Identity Anchor) -> TextStyle -> Identity TextStyle)
-> Anchor -> TextStyle -> TextStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Anchor
AnchorStart TextStyle -> (TextStyle -> TextStyle) -> TextStyle
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> TextStyle -> Identity TextStyle
forall a. IsLabel "hsize" a => a
forall (x :: Symbol) a. IsLabel x a => a
#hsize ((Double -> Identity Double) -> TextStyle -> Identity TextStyle)
-> Double -> TextStyle -> TextStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.5 TextStyle -> (TextStyle -> TextStyle) -> TextStyle
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> TextStyle -> Identity TextStyle
forall a. IsLabel "size" a => a
forall (x :: Symbol) a. IsLabel x a => a
#size ((Double -> Identity Double) -> TextStyle -> Identity TextStyle)
-> Double -> TextStyle -> TextStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.08)
            [Text
"another pretty long piece of text"]
        )
        [Double -> Double -> XY Double
forall a. a -> a -> XY a
P Double
1 Double
1]

-- | compound chart
gopts3 :: [GlyphStyle]
gopts3 :: [GlyphStyle]
gopts3 =
  (Colour -> GlyphShape -> GlyphStyle)
-> [Colour] -> [GlyphShape] -> [GlyphStyle]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith
    ( \Colour
x GlyphShape
y ->
        ((Colour -> Identity Colour) -> GlyphStyle -> Identity GlyphStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> GlyphStyle -> Identity GlyphStyle)
-> Colour -> GlyphStyle -> GlyphStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Colour
x)
          (GlyphStyle -> GlyphStyle)
-> (GlyphStyle -> GlyphStyle) -> GlyphStyle -> GlyphStyle
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ((Colour -> Identity Colour) -> GlyphStyle -> Identity GlyphStyle
forall a. IsLabel "borderColor" a => a
forall (x :: Symbol) a. IsLabel x a => a
#borderColor ((Colour -> Identity Colour) -> GlyphStyle -> Identity GlyphStyle)
-> Colour -> GlyphStyle -> GlyphStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Colour
x)
          (GlyphStyle -> GlyphStyle)
-> (GlyphStyle -> GlyphStyle) -> GlyphStyle -> GlyphStyle
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ((Double -> Identity Double) -> GlyphStyle -> Identity GlyphStyle
forall a. IsLabel "borderSize" a => a
forall (x :: Symbol) a. IsLabel x a => a
#borderSize ((Double -> Identity Double) -> GlyphStyle -> Identity GlyphStyle)
-> Double -> GlyphStyle -> GlyphStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.005)
          (GlyphStyle -> GlyphStyle)
-> (GlyphStyle -> GlyphStyle) -> GlyphStyle -> GlyphStyle
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ((GlyphShape -> Identity GlyphShape)
-> GlyphStyle -> Identity GlyphStyle
forall a. IsLabel "shape" a => a
forall (x :: Symbol) a. IsLabel x a => a
#shape ((GlyphShape -> Identity GlyphShape)
 -> GlyphStyle -> Identity GlyphStyle)
-> GlyphShape -> GlyphStyle -> GlyphStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ GlyphShape
y)
          (GlyphStyle -> GlyphStyle)
-> (GlyphStyle -> GlyphStyle) -> GlyphStyle -> GlyphStyle
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ((Double -> Identity Double) -> GlyphStyle -> Identity GlyphStyle
forall a. IsLabel "size" a => a
forall (x :: Symbol) a. IsLabel x a => a
#size ((Double -> Identity Double) -> GlyphStyle -> Identity GlyphStyle)
-> Double -> GlyphStyle -> GlyphStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.08)
          (GlyphStyle -> GlyphStyle) -> GlyphStyle -> GlyphStyle
forall a b. (a -> b) -> a -> b
$ GlyphStyle
defaultGlyphStyle
    )
    [Colour]
palette1
    [Double -> GlyphShape
EllipseGlyph Double
1.5, GlyphShape
SquareGlyph, GlyphShape
CircleGlyph]

-- | Glyph + Lines
--
-- ![glines example](other/glines.svg)
glinesExample :: ChartSvg
glinesExample :: ChartSvg
glinesExample = ChartSvg
forall a. Monoid a => a
mempty ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
& ([Chart Double] -> Identity [Chart Double])
-> ChartSvg -> Identity ChartSvg
forall a. IsLabel "chartList" a => a
forall (x :: Symbol) a. IsLabel x a => a
#chartList (([Chart Double] -> Identity [Chart Double])
 -> ChartSvg -> Identity ChartSvg)
-> [Chart Double] -> ChartSvg -> ChartSvg
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ([Chart Double]
cs [Chart Double] -> [Chart Double] -> [Chart Double]
forall a. Semigroup a => a -> a -> a
<> [Chart Double]
gs)
  where
    cs :: [Chart Double]
cs = ([Point Double] -> LineStyle -> Chart Double)
-> [[Point Double]] -> [LineStyle] -> [Chart Double]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\[Point Double]
d LineStyle
s -> Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (LineStyle -> Annotation
LineA LineStyle
s) (Point Double -> XY Double
forall a. Point a -> XY a
PointXY (Point Double -> XY Double) -> [Point Double] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Point Double]
d)) [[Point Double]]
ls [LineStyle]
lopts
    gs :: [Chart Double]
gs = ([Point Double] -> GlyphStyle -> Chart Double)
-> [[Point Double]] -> [GlyphStyle] -> [Chart Double]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\[Point Double]
d GlyphStyle
s -> Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (GlyphStyle -> Annotation
GlyphA GlyphStyle
s) (Point Double -> XY Double
forall a. Point a -> XY a
PointXY (Point Double -> XY Double) -> [Point Double] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Point Double]
d)) [[Point Double]]
ls [GlyphStyle]
gopts3

lgdata :: [(Text, Point Double)]
lgdata :: [(Text, Point Double)]
lgdata =
  (\p :: Point Int
p@(Point Int
x Int
y) -> ([Char] -> Text
pack (Int -> [Char]
forall a b. (Show a, ConvertText [Char] b) => a -> b
show Int
x [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
"," [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> Int -> [Char]
forall a b. (Show a, ConvertText [Char] b) => a -> b
show Int
y), Int -> Double
forall a b. FromIntegral a b => b -> a
fromIntegral (Int -> Double) -> Point Int -> Point Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Point Int
p))
    (Point Int -> (Text, Point Double))
-> [Point Int] -> [(Text, Point Double)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Int -> Int -> Point Int
forall a. a -> a -> Point a
Point (Int -> Int -> Point Int) -> [Int] -> [Int -> Point Int]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Int
0 .. Int
5] [Int -> Point Int] -> [Int] -> [Point Int]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [Int
0 .. Int
5] :: [Point Int])

-- | Labelled Glyphs
--
-- ![lglyph example](other/lglyph.svg)
lglyphExample :: ChartSvg
lglyphExample :: ChartSvg
lglyphExample = ChartSvg
forall a. Monoid a => a
mempty ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
& ([Chart Double] -> Identity [Chart Double])
-> ChartSvg -> Identity ChartSvg
forall a. IsLabel "chartList" a => a
forall (x :: Symbol) a. IsLabel x a => a
#chartList (([Chart Double] -> Identity [Chart Double])
 -> ChartSvg -> Identity ChartSvg)
-> [Chart Double] -> ChartSvg -> ChartSvg
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ([Chart Double]
txt [Chart Double] -> [Chart Double] -> [Chart Double]
forall a. Semigroup a => a -> a -> a
<> [Chart Double]
gly)
  where
    txt :: [Chart Double]
txt =
      ( \(Text
t, Point Double
p) ->
          Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart
            ( TextStyle -> [Text] -> Annotation
TextA
                ( TextStyle
defaultTextStyle
                    TextStyle -> (TextStyle -> TextStyle) -> TextStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> TextStyle -> Identity TextStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> TextStyle -> Identity TextStyle)
-> (Colour -> Colour) -> TextStyle -> TextStyle
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ Double -> Colour -> Colour
setOpac Double
0.2
                )
                [Text
t]
            )
            (Point Double -> XY Double
forall a. Point a -> XY a
PointXY (Point Double -> XY Double) -> [Point Double] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Point Double
p Point Double -> Point Double -> Point Double
forall a. Additive a => a -> a -> a
+ Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
0 Double
0.2])
      )
        ((Text, Point Double) -> Chart Double)
-> [(Text, Point Double)] -> [Chart Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Text, Point Double)]
lgdata
    gly :: [Chart Double]
gly =
      ( \Point Double
d ->
          Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart
            ( GlyphStyle -> Annotation
GlyphA
                ( GlyphStyle
defaultGlyphStyle
                    GlyphStyle -> (GlyphStyle -> GlyphStyle) -> GlyphStyle
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> GlyphStyle -> Identity GlyphStyle
forall a. IsLabel "size" a => a
forall (x :: Symbol) a. IsLabel x a => a
#size ((Double -> Identity Double) -> GlyphStyle -> Identity GlyphStyle)
-> Double -> GlyphStyle -> GlyphStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.01
                    GlyphStyle -> (GlyphStyle -> GlyphStyle) -> GlyphStyle
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> GlyphStyle -> Identity GlyphStyle
forall a. IsLabel "borderSize" a => a
forall (x :: Symbol) a. IsLabel x a => a
#borderSize ((Double -> Identity Double) -> GlyphStyle -> Identity GlyphStyle)
-> Double -> GlyphStyle -> GlyphStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0
                    GlyphStyle -> (GlyphStyle -> GlyphStyle) -> GlyphStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> GlyphStyle -> Identity GlyphStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> GlyphStyle -> Identity GlyphStyle)
-> Colour -> GlyphStyle -> GlyphStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [Colour]
palette1 [Colour] -> Int -> Colour
forall a. [a] -> Int -> a
List.!! Int
2
                )
            )
            (Point Double -> XY Double
forall a. Point a -> XY a
PointXY (Point Double -> XY Double) -> [Point Double] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Point Double
d])
      )
        (Point Double -> Chart Double) -> [Point Double] -> [Chart Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((Text, Point Double) -> Point Double
forall a b. (a, b) -> b
snd ((Text, Point Double) -> Point Double)
-> [(Text, Point Double)] -> [Point Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Text, Point Double)]
lgdata)

-- | mappend of lglyph and glines examples
--
-- ![compound example](other/compound.svg)
compoundExample :: ChartSvg
compoundExample :: ChartSvg
compoundExample = ChartSvg
lglyphExample ChartSvg -> ChartSvg -> ChartSvg
forall a. Semigroup a => a -> a -> a
<> ChartSvg
glinesExample

-- | label example.
--
-- ![label example](other/label.svg)
labelExample :: ChartSvg
labelExample :: ChartSvg
labelExample =
  ChartSvg
forall a. Monoid a => a
mempty ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
& ([Chart Double] -> Identity [Chart Double])
-> ChartSvg -> Identity ChartSvg
forall a. IsLabel "chartList" a => a
forall (x :: Symbol) a. IsLabel x a => a
#chartList
    (([Chart Double] -> Identity [Chart Double])
 -> ChartSvg -> Identity ChartSvg)
-> [Chart Double] -> ChartSvg -> ChartSvg
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (TextStyle -> [Text] -> Annotation
TextA (TextStyle
defaultTextStyle TextStyle -> (TextStyle -> TextStyle) -> TextStyle
forall a b. a -> (a -> b) -> b
& (Maybe Double -> Identity (Maybe Double))
-> TextStyle -> Identity TextStyle
forall a. IsLabel "rotation" a => a
forall (x :: Symbol) a. IsLabel x a => a
#rotation ((Maybe Double -> Identity (Maybe Double))
 -> TextStyle -> Identity TextStyle)
-> Double -> TextStyle -> TextStyle
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ -Double
forall a. TrigField a => a
piDouble -> Double -> Double
forall a. Divisive a => a -> a -> a
/Double
4) [Text
"text at (1,1) rotated by -(pi/4) radians"]) [Point Double -> XY Double
forall a. Point a -> XY a
PointXY (Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
1.0 Double
1.0)]]

-- | legend test
--
-- ![legend example](other/legend.svg)
legendExample :: ChartSvg
legendExample :: ChartSvg
legendExample =
  ChartSvg
forall a. Monoid a => a
mempty ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
& (HudOptions -> Identity HudOptions)
-> ChartSvg -> Identity ChartSvg
forall a. IsLabel "hudOptions" a => a
forall (x :: Symbol) a. IsLabel x a => a
#hudOptions
    ((HudOptions -> Identity HudOptions)
 -> ChartSvg -> Identity ChartSvg)
-> HudOptions -> ChartSvg -> ChartSvg
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ( HudOptions
defaultHudOptions
           HudOptions -> (HudOptions -> HudOptions) -> HudOptions
forall a b. a -> (a -> b) -> b
& (Maybe (LegendOptions, [(Annotation, Text)])
 -> Identity (Maybe (LegendOptions, [(Annotation, Text)])))
-> HudOptions -> Identity HudOptions
forall a. IsLabel "hudLegend" a => a
forall (x :: Symbol) a. IsLabel x a => a
#hudLegend
           ((Maybe (LegendOptions, [(Annotation, Text)])
  -> Identity (Maybe (LegendOptions, [(Annotation, Text)])))
 -> HudOptions -> Identity HudOptions)
-> (LegendOptions, [(Annotation, Text)])
-> HudOptions
-> HudOptions
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ ( LegendOptions
defaultLegendOptions
                  LegendOptions -> (LegendOptions -> LegendOptions) -> LegendOptions
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double)
-> LegendOptions -> Identity LegendOptions
forall a. IsLabel "lscale" a => a
forall (x :: Symbol) a. IsLabel x a => a
#lscale ((Double -> Identity Double)
 -> LegendOptions -> Identity LegendOptions)
-> Double -> LegendOptions -> LegendOptions
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.3
                  LegendOptions -> (LegendOptions -> LegendOptions) -> LegendOptions
forall a b. a -> (a -> b) -> b
& (Place -> Identity Place)
-> LegendOptions -> Identity LegendOptions
forall a. IsLabel "lplace" a => a
forall (x :: Symbol) a. IsLabel x a => a
#lplace ((Place -> Identity Place)
 -> LegendOptions -> Identity LegendOptions)
-> Place -> LegendOptions -> LegendOptions
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Point Double -> Place
PlaceAbsolute (Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
0.0 Double
0.0)
                  LegendOptions -> (LegendOptions -> LegendOptions) -> LegendOptions
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double)
-> LegendOptions -> Identity LegendOptions
forall a. IsLabel "lsize" a => a
forall (x :: Symbol) a. IsLabel x a => a
#lsize ((Double -> Identity Double)
 -> LegendOptions -> Identity LegendOptions)
-> Double -> LegendOptions -> LegendOptions
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.12
                  LegendOptions -> (LegendOptions -> LegendOptions) -> LegendOptions
forall a b. a -> (a -> b) -> b
& (TextStyle -> Identity TextStyle)
-> LegendOptions -> Identity LegendOptions
forall a. IsLabel "ltext" a => a
forall (x :: Symbol) a. IsLabel x a => a
#ltext ((TextStyle -> Identity TextStyle)
 -> LegendOptions -> Identity LegendOptions)
-> ((Double -> Identity Double) -> TextStyle -> Identity TextStyle)
-> (Double -> Identity Double)
-> LegendOptions
-> Identity LegendOptions
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Double -> Identity Double) -> TextStyle -> Identity TextStyle
forall a. IsLabel "size" a => a
forall (x :: Symbol) a. IsLabel x a => a
#size ((Double -> Identity Double)
 -> LegendOptions -> Identity LegendOptions)
-> Double -> LegendOptions -> LegendOptions
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.16,
                [(Annotation, Text)]
l1
              )
       )
  where
    l1 :: [(Annotation, Text)]
l1 =
      [ (GlyphStyle -> Annotation
GlyphA GlyphStyle
defaultGlyphStyle, Text
"glyph"),
        (RectStyle -> Annotation
RectA RectStyle
defaultRectStyle, Text
"rect"),
        (TextStyle -> [Text] -> Annotation
TextA (TextStyle
defaultTextStyle TextStyle -> (TextStyle -> TextStyle) -> TextStyle
forall a b. a -> (a -> b) -> b
& (Anchor -> Identity Anchor) -> TextStyle -> Identity TextStyle
forall a. IsLabel "anchor" a => a
forall (x :: Symbol) a. IsLabel x a => a
#anchor ((Anchor -> Identity Anchor) -> TextStyle -> Identity TextStyle)
-> Anchor -> TextStyle -> TextStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Anchor
AnchorStart) [Text
"content"], Text
"text"),
        (LineStyle -> Annotation
LineA LineStyle
defaultLineStyle, Text
"line"),
        (GlyphStyle -> Annotation
GlyphA GlyphStyle
defaultGlyphStyle, Text
"abcdefghijklmnopqrst"),
        (Annotation
BlankA, Text
"blank")
      ]

-- | wave example
--
-- ![wave example](other/wave.svg)
waveExample :: ChartSvg
waveExample :: ChartSvg
waveExample = ChartSvg
forall a. Monoid a => a
mempty ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
& ([Chart Double] -> Identity [Chart Double])
-> ChartSvg -> Identity ChartSvg
forall a. IsLabel "chartList" a => a
forall (x :: Symbol) a. IsLabel x a => a
#chartList (([Chart Double] -> Identity [Chart Double])
 -> ChartSvg -> Identity ChartSvg)
-> [Chart Double] -> ChartSvg -> ChartSvg
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (GlyphStyle -> Annotation
GlyphA GlyphStyle
defaultGlyphStyle) (Point Double -> XY Double
forall a. Point a -> XY a
PointXY (Point Double -> XY Double) -> [Point Double] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Double -> Double)
-> Range Double -> Grid (Range Double) -> [Point Double]
forall a.
FieldSpace (Range a) =>
(a -> a) -> Range a -> Grid (Range a) -> [Point a]
gridP Double -> Double
forall a. TrigField a => a -> a
sin (Double -> Double -> Range Double
forall a. a -> a -> Range a
Range Double
0 (Double
2 Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double
forall a. TrigField a => a
pi)) Grid (Range Double)
30)]

-- | venn diagram
--
-- ![venn diagram](other/venn.svg)
vennExample :: ChartSvg
vennExample :: ChartSvg
vennExample =
  ChartSvg
forall a. Monoid a => a
mempty ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
&
  #chartList .~ zipWith (\c x -> Chart (PathA (defaultPathStyle & #color .~ setOpac 0.2 c) (fst <$> x)) (PointXY . snd <$> x)) palette1 (toPathXYs . parsePath <$> vennSegs) &
  #svgOptions .~ (defaultSvgOptions & #chartAspect .~ FixedAspect 1) &
  #hudOptions .~ defaultHudOptions

{-
These were originally based on:

    [ ("origin", Point 0 0), -- origin
      ("circle1", Point 0.5 (-0.5 + cos (pi / 6))), -- center of circle 1
      ("circle2", Point 0 -0.5), -- center of circle 2
      ("circle3", Point -0.5 (-0.5 + cos (pi / 6))), -- center of circle 3
      ("corner1", Point 0 (-0.5 + 2 * cos (pi / 6))), -- corner 1
      ("corner2", Point 1 -0.5), -- corner 2
      ("corner3", Point -1 -0.5) -- corner 3
    ]
-}
vennSegs :: [Text]
vennSegs :: [Text]
vennSegs =
      [ Text
"M0.0,-1.2320508075688774 A0.5 0.5 0.0 1 1 1.0,0.5 1.0 1.0 0.0 0 0 0.5,-0.3660254037844387 1.0 1.0 0.0 0 0 0.0,-1.2320508075688774 Z",
        Text
"M-1.0,0.5 A0.5 0.5 0.0 1 0 1.0,0.5 1.0 1.0 0.0 0 1 0.0,0.5 1.0 1.0 0.0 0 1 -1.0,0.5 Z",
        Text
"M-1.0,0.5 A0.5 0.5 0.0 1 1 0.0,-1.2320508075688774 1.0 1.0 0.0 0 0 -0.5,-0.3660254037844387 1.0 1.0 0.0 0 0 -1.0,0.5 Z",
        Text
"M0.5,-0.3660254037844387 A1.0 1.0 0.0 0 1 1.0,0.5 1.0 1.0 0.0 0 1 0.0,0.5 1.0 1.0 0.0 0 0 0.5,-0.3660254037844387 Z",
        Text
"M0.0,0.5 A1.0 1.0 0.0 0 1 -1.0,0.5 1.0 1.0 0.0 0 1 -0.5,-0.3660254037844387 1.0 1.0 0.0 0 0 0.0,0.5 Z",
        Text
"M0.0,-1.2320508075688774 A1.0 1.0 0.0 0 1 0.5,-0.3660254037844387 1.0 1.0 0.0 0 0 -0.5,-0.3660254037844387 1.0 1.0 0.0 0 1 0.0,-1.2320508075688774 Z",
        Text
"M0.5,-0.3660254037844387 A1.0 1.0 0.0 0 1 0.0,0.5 1.0 1.0 0.0 0 1 -0.5,-0.3660254037844387 1.0 1.0 0.0 0 1 0.5,-0.3660254037844387 Z"
      ]

-- | Compound path example.
--
-- ![path test](other/path.svg)
pathExample :: ChartSvg
pathExample :: ChartSvg
pathExample =
  ChartSvg
forall a. Monoid a => a
mempty ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
&
   #chartList .~ [path', c0] &
   #hudOptions .~ defaultHudOptions &
   #svgOptions %~
   ((#outerPad ?~ 0.1) .
    (#chartAspect .~ ChartAspect))
  where
    ps :: [(PathInfo Double, Point Double)]
ps =
      [
        (PathInfo Double
forall a. PathInfo a
StartI, Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
0 Double
0),
        (PathInfo Double
forall a. PathInfo a
LineI, Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
1 Double
0),
        (Point Double -> Point Double -> PathInfo Double
forall a. Point a -> Point a -> PathInfo a
CubicI (Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
0.2 Double
0) (Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
0.25 Double
1), Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
1 Double
1),
        (Point Double -> PathInfo Double
forall a. Point a -> PathInfo a
QuadI (Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
-1 Double
2), Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
0 Double
1),
        (ArcInfo Double -> PathInfo Double
forall a. ArcInfo a -> PathInfo a
ArcI (Point Double -> Double -> Bool -> Bool -> ArcInfo Double
forall a. Point a -> a -> Bool -> Bool -> ArcInfo a
ArcInfo (Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
1 Double
1) (-Double
forall a. TrigField a => a
piDouble -> Double -> Double
forall a. Divisive a => a -> a -> a
/Double
6) Bool
False Bool
False), Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
0 Double
0)
      ]
    path' :: Chart Double
path' = Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (PathStyle -> [PathInfo Double] -> Annotation
PathA (PathStyle
defaultPathStyle PathStyle -> (PathStyle -> PathStyle) -> PathStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> PathStyle -> Identity PathStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> PathStyle -> Identity PathStyle)
-> Colour -> PathStyle -> PathStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double -> Colour -> Colour
setOpac Double
0.1 ([Colour]
palette1 [Colour] -> Int -> Colour
forall a. [a] -> Int -> a
List.!! Int
2) PathStyle -> (PathStyle -> PathStyle) -> PathStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> PathStyle -> Identity PathStyle
forall a. IsLabel "borderColor" a => a
forall (x :: Symbol) a. IsLabel x a => a
#borderColor ((Colour -> Identity Colour) -> PathStyle -> Identity PathStyle)
-> Colour -> PathStyle -> PathStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double -> Double -> Double -> Double -> Colour
Colour Double
0.2 Double
0.8 Double
0.4 Double
0.3) ((PathInfo Double, Point Double) -> PathInfo Double
forall a b. (a, b) -> a
fst ((PathInfo Double, Point Double) -> PathInfo Double)
-> [(PathInfo Double, Point Double)] -> [PathInfo Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(PathInfo Double, Point Double)]
ps)) (Point Double -> XY Double
forall a. Point a -> XY a
PointXY (Point Double -> XY Double)
-> ((PathInfo Double, Point Double) -> Point Double)
-> (PathInfo Double, Point Double)
-> XY Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (PathInfo Double, Point Double) -> Point Double
forall a b. (a, b) -> b
snd ((PathInfo Double, Point Double) -> XY Double)
-> [(PathInfo Double, Point Double)] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(PathInfo Double, Point Double)]
ps)
    c0 :: Chart Double
c0 = Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (GlyphStyle -> Annotation
GlyphA GlyphStyle
defaultGlyphStyle) (Point Double -> XY Double
forall a. Point a -> XY a
PointXY (Point Double -> XY Double)
-> ((PathInfo Double, Point Double) -> Point Double)
-> (PathInfo Double, Point Double)
-> XY Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (PathInfo Double, Point Double) -> Point Double
forall a b. (a, b) -> b
snd ((PathInfo Double, Point Double) -> XY Double)
-> [(PathInfo Double, Point Double)] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(PathInfo Double, Point Double)]
ps)

-- | ellipse example
--
-- (ArcPosition (Point 1 0) (Point 0 1) (ArcInfo (Point 1.5 1) 0 True True))
--
-- ![ellipse example](other/ellipse.svg)
--
ellipseExample :: ChartSvg
ellipseExample :: ChartSvg
ellipseExample =
  ChartSvg
forall a. Monoid a => a
mempty ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
&
   #chartList .~ [ell, ellFull, c0, bbox, xradii, yradii] &
   #hudOptions .~ defaultHudOptions &
   #svgOptions %~ ((#outerPad .~ Nothing) . (#chartAspect .~ UnadjustedAspect))
  where
    p :: ArcPosition Double
p@(ArcPosition Point Double
p1 Point Double
p2 ArcInfo Double
_) = Point Double
-> Point Double -> ArcInfo Double -> ArcPosition Double
forall a. Point a -> Point a -> ArcInfo a -> ArcPosition a
ArcPosition (Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
1 Double
0) (Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
0 Double
1) (Point Double -> Double -> Bool -> Bool -> ArcInfo Double
forall a. Point a -> a -> Bool -> Bool -> ArcInfo a
ArcInfo (Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
1.5 Double
1) (Double
forall a. TrigField a => a
piDouble -> Double -> Double
forall a. Divisive a => a -> a -> a
/Double
3) Bool
True Bool
True)
    (ArcCentroid Point Double
c Point Double
r Double
phi' Double
ang0 Double
angd) = ArcPosition Double -> ArcCentroid Double
forall a.
(FromInteger a, Ord a, TrigField a, ExpField a) =>
ArcPosition a -> ArcCentroid a
arcCentroid ArcPosition Double
p
    ellFull :: Chart Double
ellFull = Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (LineStyle -> Annotation
LineA (LineStyle -> Annotation) -> LineStyle -> Annotation
forall a b. (a -> b) -> a -> b
$ LineStyle
defaultLineStyle LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> LineStyle -> Identity LineStyle
forall a. IsLabel "width" a => a
forall (x :: Symbol) a. IsLabel x a => a
#width ((Double -> Identity Double) -> LineStyle -> Identity LineStyle)
-> Double -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.002 LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> LineStyle -> Identity LineStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> LineStyle -> Identity LineStyle)
-> Colour -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ([Colour]
palette1 [Colour] -> Int -> Colour
forall a. [a] -> Int -> a
List.!! Int
1)) (Point Double -> XY Double
forall a. Point a -> XY a
PointXY (Point Double -> XY Double)
-> (Double -> Point Double) -> Double -> XY Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Point Double -> Point Double -> Double -> Double -> Point Double
forall b a.
(Direction b a, Affinity b a, TrigField a) =>
b -> b -> a -> a -> b
ellipse Point Double
c Point Double
r Double
phi' (Double -> Point Double)
-> (Double -> Double) -> Double -> Point Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (\Double
x -> Double
2 Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double
forall a. TrigField a => a
pi Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double
x Double -> Double -> Double
forall a. Divisive a => a -> a -> a
/ Double
100.0) (Double -> XY Double) -> [Double] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Double
0..Double
100])
    ell :: Chart Double
ell = Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (LineStyle -> Annotation
LineA (LineStyle -> Annotation) -> LineStyle -> Annotation
forall a b. (a -> b) -> a -> b
$ LineStyle
defaultLineStyle LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> LineStyle -> Identity LineStyle
forall a. IsLabel "width" a => a
forall (x :: Symbol) a. IsLabel x a => a
#width ((Double -> Identity Double) -> LineStyle -> Identity LineStyle)
-> Double -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.002 LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> LineStyle -> Identity LineStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> LineStyle -> Identity LineStyle)
-> Colour -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ([Colour]
palette1 [Colour] -> Int -> Colour
forall a. [a] -> Int -> a
List.!! Int
1)) (Point Double -> XY Double
forall a. Point a -> XY a
PointXY (Point Double -> XY Double)
-> (Double -> Point Double) -> Double -> XY Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Point Double -> Point Double -> Double -> Double -> Point Double
forall b a.
(Direction b a, Affinity b a, TrigField a) =>
b -> b -> a -> a -> b
ellipse Point Double
c Point Double
r Double
phi' (Double -> Point Double)
-> (Double -> Double) -> Double -> Point Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (\Double
x -> Double
ang0 Double -> Double -> Double
forall a. Additive a => a -> a -> a
+ Double
angd Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double
x Double -> Double -> Double
forall a. Divisive a => a -> a -> a
/ Double
100.0) (Double -> XY Double) -> [Double] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Double
0..Double
100])
    c0 :: Chart Double
c0 = Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (GlyphStyle -> Annotation
GlyphA GlyphStyle
defaultGlyphStyle) (Point Double -> XY Double
forall a. Point a -> XY a
PointXY (Point Double -> XY Double) -> [Point Double] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Point Double
c,Point Double
p1,Point Double
p2])
    bbox :: Chart Double
bbox = Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (RectStyle -> Annotation
RectA (RectStyle -> Annotation) -> RectStyle -> Annotation
forall a b. (a -> b) -> a -> b
$ RectStyle
defaultRectStyle RectStyle -> (RectStyle -> RectStyle) -> RectStyle
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> RectStyle -> Identity RectStyle
forall a. IsLabel "borderSize" a => a
forall (x :: Symbol) a. IsLabel x a => a
#borderSize ((Double -> Identity Double) -> RectStyle -> Identity RectStyle)
-> Double -> RectStyle -> RectStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.002 RectStyle -> (RectStyle -> RectStyle) -> RectStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> RectStyle -> Identity RectStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> RectStyle -> Identity RectStyle)
-> Colour -> RectStyle -> RectStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double -> Double -> Double -> Double -> Colour
Colour Double
0.4 Double
0.4 Double
0.8 Double
0.1 RectStyle -> (RectStyle -> RectStyle) -> RectStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> RectStyle -> Identity RectStyle
forall a. IsLabel "borderColor" a => a
forall (x :: Symbol) a. IsLabel x a => a
#borderColor ((Colour -> Identity Colour) -> RectStyle -> Identity RectStyle)
-> Colour -> RectStyle -> RectStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double -> Double -> Double -> Double -> Colour
Colour Double
0.5 Double
0.5 Double
0.5 Double
1) [Rect Double -> XY Double
forall a. Rect a -> XY a
RectXY (ArcPosition Double -> Rect Double
arcBox ArcPosition Double
p)]
    xradii :: Chart Double
xradii = Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (LineStyle -> Annotation
LineA (LineStyle -> Annotation) -> LineStyle -> Annotation
forall a b. (a -> b) -> a -> b
$ LineStyle
defaultLineStyle LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> LineStyle -> Identity LineStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> LineStyle -> Identity LineStyle)
-> Colour -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double -> Double -> Double -> Double -> Colour
Colour Double
0.9 Double
0.2 Double
0.02 Double
1 LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> LineStyle -> Identity LineStyle
forall a. IsLabel "width" a => a
forall (x :: Symbol) a. IsLabel x a => a
#width ((Double -> Identity Double) -> LineStyle -> Identity LineStyle)
-> Double -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.005 LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Maybe [Double] -> Identity (Maybe [Double]))
-> LineStyle -> Identity LineStyle
forall a. IsLabel "dasharray" a => a
forall (x :: Symbol) a. IsLabel x a => a
#dasharray ((Maybe [Double] -> Identity (Maybe [Double]))
 -> LineStyle -> Identity LineStyle)
-> Maybe [Double] -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [Double] -> Maybe [Double]
forall a. a -> Maybe a
Just [Double
0.03, Double
0.01] LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Maybe LineCap -> Identity (Maybe LineCap))
-> LineStyle -> Identity LineStyle
forall a. IsLabel "linecap" a => a
forall (x :: Symbol) a. IsLabel x a => a
#linecap ((Maybe LineCap -> Identity (Maybe LineCap))
 -> LineStyle -> Identity LineStyle)
-> Maybe LineCap -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ LineCap -> Maybe LineCap
forall a. a -> Maybe a
Just LineCap
LineCapRound) (Point Double -> XY Double
forall a. Point a -> XY a
PointXY (Point Double -> XY Double) -> [Point Double] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Point Double -> Point Double -> Double -> Double -> Point Double
forall b a.
(Direction b a, Affinity b a, TrigField a) =>
b -> b -> a -> a -> b
ellipse Point Double
c Point Double
r Double
phi' Double
0, Point Double -> Point Double -> Double -> Double -> Point Double
forall b a.
(Direction b a, Affinity b a, TrigField a) =>
b -> b -> a -> a -> b
ellipse Point Double
c Point Double
r Double
phi' Double
forall a. TrigField a => a
pi])
    yradii :: Chart Double
yradii = Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (LineStyle -> Annotation
LineA (LineStyle -> Annotation) -> LineStyle -> Annotation
forall a b. (a -> b) -> a -> b
$ LineStyle
defaultLineStyle LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> LineStyle -> Identity LineStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> LineStyle -> Identity LineStyle)
-> Colour -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double -> Double -> Double -> Double -> Colour
Colour Double
0.9 Double
0.9 Double
0.02 Double
1 LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> LineStyle -> Identity LineStyle
forall a. IsLabel "width" a => a
forall (x :: Symbol) a. IsLabel x a => a
#width ((Double -> Identity Double) -> LineStyle -> Identity LineStyle)
-> Double -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.005 LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Maybe [Double] -> Identity (Maybe [Double]))
-> LineStyle -> Identity LineStyle
forall a. IsLabel "dasharray" a => a
forall (x :: Symbol) a. IsLabel x a => a
#dasharray ((Maybe [Double] -> Identity (Maybe [Double]))
 -> LineStyle -> Identity LineStyle)
-> Maybe [Double] -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [Double] -> Maybe [Double]
forall a. a -> Maybe a
Just [Double
0.03, Double
0.01] LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Maybe LineCap -> Identity (Maybe LineCap))
-> LineStyle -> Identity LineStyle
forall a. IsLabel "linecap" a => a
forall (x :: Symbol) a. IsLabel x a => a
#linecap ((Maybe LineCap -> Identity (Maybe LineCap))
 -> LineStyle -> Identity LineStyle)
-> Maybe LineCap -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ LineCap -> Maybe LineCap
forall a. a -> Maybe a
Just LineCap
LineCapRound) (Point Double -> XY Double
forall a. Point a -> XY a
PointXY (Point Double -> XY Double) -> [Point Double] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Point Double -> Point Double -> Double -> Double -> Point Double
forall b a.
(Direction b a, Affinity b a, TrigField a) =>
b -> b -> a -> a -> b
ellipse Point Double
c Point Double
r Double
phi' (Double
forall a. TrigField a => a
piDouble -> Double -> Double
forall a. Divisive a => a -> a -> a
/Double
2), Point Double -> Point Double -> Double -> Double -> Point Double
forall b a.
(Direction b a, Affinity b a, TrigField a) =>
b -> b -> a -> a -> b
ellipse Point Double
c Point Double
r Double
phi' (Double
3Double -> Double -> Double
forall a. Divisive a => a -> a -> a
/Double
2Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
*Double
forall a. TrigField a => a
pi)])

-- | arc example
--
-- ![arc example](other/arc.svg)
--
-- There is a bug for rotated ellipses. See 'problematic2' for scaling issue when phi is non-zero.
--
arcExample :: ChartSvg
arcExample :: ChartSvg
arcExample =
  ChartSvg
forall a. Monoid a => a
mempty ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
&
   #chartList .~ [arc, ell, c0, bbox] &
   #hudOptions .~ defaultHudOptions &
   #svgOptions %~ ((#outerPad .~ Nothing) . (#chartAspect .~ FixedAspect 1))
  where
    p1 :: ArcPosition Double
p1 = Point Double
-> Point Double -> ArcInfo Double -> ArcPosition Double
forall a. Point a -> Point a -> ArcInfo a -> ArcPosition a
ArcPosition (Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
1.0 Double
0.0) (Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
0.0 Double
1.0) (Point Double -> Double -> Bool -> Bool -> ArcInfo Double
forall a. Point a -> a -> Bool -> Bool -> ArcInfo a
ArcInfo (Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
1.0 Double
0.5) Double
0 Bool
False Bool
True)
    ps :: [(PathInfo Double, Point Double)]
ps = ArcPosition Double -> [(PathInfo Double, Point Double)]
singletonArc ArcPosition Double
p1
    (ArcCentroid Point Double
c Point Double
r Double
phi' Double
ang0 Double
angd) = ArcPosition Double -> ArcCentroid Double
forall a.
(FromInteger a, Ord a, TrigField a, ExpField a) =>
ArcPosition a -> ArcCentroid a
arcCentroid ArcPosition Double
p1
    arc :: Chart Double
arc = Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (PathStyle -> [PathInfo Double] -> Annotation
PathA (PathStyle
defaultPathStyle PathStyle -> (PathStyle -> PathStyle) -> PathStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> PathStyle -> Identity PathStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> PathStyle -> Identity PathStyle)
-> Colour -> PathStyle -> PathStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double -> Colour -> Colour
setOpac Double
0.1 ([Colour]
palette1 [Colour] -> Int -> Colour
forall a. [a] -> Int -> a
List.!! Int
2) PathStyle -> (PathStyle -> PathStyle) -> PathStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> PathStyle -> Identity PathStyle
forall a. IsLabel "borderColor" a => a
forall (x :: Symbol) a. IsLabel x a => a
#borderColor ((Colour -> Identity Colour) -> PathStyle -> Identity PathStyle)
-> Colour -> PathStyle -> PathStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Colour
transparent) ((PathInfo Double, Point Double) -> PathInfo Double
forall a b. (a, b) -> a
fst ((PathInfo Double, Point Double) -> PathInfo Double)
-> [(PathInfo Double, Point Double)] -> [PathInfo Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(PathInfo Double, Point Double)]
ps)) (Point Double -> XY Double
forall a. Point a -> XY a
PointXY (Point Double -> XY Double)
-> ((PathInfo Double, Point Double) -> Point Double)
-> (PathInfo Double, Point Double)
-> XY Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (PathInfo Double, Point Double) -> Point Double
forall a b. (a, b) -> b
snd ((PathInfo Double, Point Double) -> XY Double)
-> [(PathInfo Double, Point Double)] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(PathInfo Double, Point Double)]
ps)
    ell :: Chart Double
ell = Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (LineStyle -> Annotation
LineA (LineStyle -> Annotation) -> LineStyle -> Annotation
forall a b. (a -> b) -> a -> b
$ LineStyle
defaultLineStyle LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> LineStyle -> Identity LineStyle
forall a. IsLabel "width" a => a
forall (x :: Symbol) a. IsLabel x a => a
#width ((Double -> Identity Double) -> LineStyle -> Identity LineStyle)
-> Double -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.002 LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> LineStyle -> Identity LineStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> LineStyle -> Identity LineStyle)
-> Colour -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ([Colour]
palette1 [Colour] -> Int -> Colour
forall a. [a] -> Int -> a
List.!! Int
1)) (Point Double -> XY Double
forall a. Point a -> XY a
PointXY (Point Double -> XY Double)
-> (Double -> Point Double) -> Double -> XY Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Point Double -> Point Double -> Double -> Double -> Point Double
forall b a.
(Direction b a, Affinity b a, TrigField a) =>
b -> b -> a -> a -> b
ellipse Point Double
c Point Double
r Double
phi' (Double -> Point Double)
-> (Double -> Double) -> Double -> Point Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (\Double
x -> Double
ang0 Double -> Double -> Double
forall a. Additive a => a -> a -> a
+ Double
angd Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double
x Double -> Double -> Double
forall a. Divisive a => a -> a -> a
/ Double
100.0) (Double -> XY Double) -> [Double] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Double
0..Double
100])
    c0 :: Chart Double
c0 = Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (GlyphStyle -> Annotation
GlyphA GlyphStyle
defaultGlyphStyle) [Point Double -> XY Double
forall a. Point a -> XY a
PointXY Point Double
c]
    bbox :: Chart Double
bbox = Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (RectStyle -> Annotation
RectA (RectStyle -> Annotation) -> RectStyle -> Annotation
forall a b. (a -> b) -> a -> b
$ RectStyle
defaultRectStyle RectStyle -> (RectStyle -> RectStyle) -> RectStyle
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> RectStyle -> Identity RectStyle
forall a. IsLabel "borderSize" a => a
forall (x :: Symbol) a. IsLabel x a => a
#borderSize ((Double -> Identity Double) -> RectStyle -> Identity RectStyle)
-> Double -> RectStyle -> RectStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.002 RectStyle -> (RectStyle -> RectStyle) -> RectStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> RectStyle -> Identity RectStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> RectStyle -> Identity RectStyle)
-> Colour -> RectStyle -> RectStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double -> Double -> Double -> Double -> Colour
Colour Double
0.4 Double
0.4 Double
0.8 Double
0.1 RectStyle -> (RectStyle -> RectStyle) -> RectStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> RectStyle -> Identity RectStyle
forall a. IsLabel "borderColor" a => a
forall (x :: Symbol) a. IsLabel x a => a
#borderColor ((Colour -> Identity Colour) -> RectStyle -> Identity RectStyle)
-> Colour -> RectStyle -> RectStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double -> Double -> Double -> Double -> Colour
Colour Double
0.5 Double
0.5 Double
0.5 Double
1) [Rect Double -> XY Double
forall a. Rect a -> XY a
RectXY (ArcPosition Double -> Rect Double
arcBox ArcPosition Double
p1)]

-- | Reproduction of the flag explanation chart in <https://developer.mozilla.org/en-US/docs/Web/SVG/Tutorial/Paths>
--
-- ![arc flags example](other/arcflags.svg)
arcFlagsExample :: ChartSvg
arcFlagsExample :: ChartSvg
arcFlagsExample =
  ChartSvg
forall a. Monoid a => a
mempty ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
&
   #chartList .~
     vert 0.02
     [hori 0.02
       [ [Chart BlankA [R -0.4 0.4 -1 5],
          Chart (TextA (defaultTextStyle & #size .~ 0.6 & #rotation .~ Just (pi/2)) ["Sweep"]) [P 0.1 2]],
         vert 0.02
         [[Chart BlankA [R -0.25 0.25 -1 2],
           Chart (TextA (defaultTextStyle & #size .~ 0.4 & #rotation .~ Just (pi/2)) ["True"]) [P 0.1 0.5]],
          [Chart BlankA [R -0.25 0.25 -1 2],
           Chart (TextA (defaultTextStyle & #size .~ 0.4 & #rotation .~ Just (pi/2)) ["False"]) [P 0.1 0.5]]
       ],
         vert 0.02
         [checkFlags False True (setOpac 0.3 dark) & view #chartList,
          checkFlags False False (setOpac 0.3 dark) & view #chartList,
          [Chart BlankA [R -1 2 -0.25 0.25],
           Chart (TextA (defaultTextStyle & #size .~ 0.4) ["False"]) [P 0.5 -0.1]]
         ],
         vert 0.02
         [checkFlags True True (setOpac 0.3 dark) & view #chartList,
          checkFlags True False (setOpac 0.3 dark) & view #chartList,
           [Chart BlankA [R -1 2 -0.25 0.25],
            Chart (TextA (defaultTextStyle & #size .~ 0.4) ["True"]) [P 0.5 -0.1]]
         ]
       ],
      [ Chart BlankA [R 0 9 -2.75 -3.25],
        Chart (TextA (defaultTextStyle & #size .~ 0.6) ["Large"]) [P 5.5 -3.0]]
      ] ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
&
   #hudOptions .~ mempty &
   #svgOptions %~ ((#outerPad .~ Nothing) . (#chartAspect .~ UnadjustedAspect))

checkFlags :: Bool -> Bool -> Colour -> ChartSvg
checkFlags :: Bool -> Bool -> Colour -> ChartSvg
checkFlags Bool
large Bool
sweep Colour
co =
  ChartSvg
forall a. Monoid a => a
mempty ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
&
  #hudOptions .~ defaultHudOptions &
  #svgOptions . #chartAspect .~ UnadjustedAspect &
  #chartList .~ [c1, c2, ell, arc1]
  where
    c :: Point Double
c = Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
1.0 Double
1.0
    p1 :: ArcPosition Double
p1 = Point Double
-> Point Double -> ArcInfo Double -> ArcPosition Double
forall a. Point a -> Point a -> ArcInfo a -> ArcPosition a
ArcPosition (Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
0.0 Double
1.0) (Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
1.0 Double
0.0) (Point Double -> Double -> Bool -> Bool -> ArcInfo Double
forall a. Point a -> a -> Bool -> Bool -> ArcInfo a
ArcInfo (Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
1.0 Double
1.0) Double
0 Bool
large Bool
sweep)
    ps1 :: [(PathInfo Double, Point Double)]
ps1 = Point Double
-> ArcPosition Double -> [(PathInfo Double, Point Double)]
singletonPie' Point Double
c ArcPosition Double
p1
    (ArcCentroid Point Double
c' Point Double
r Double
phi' Double
ang0 Double
angd) = ArcPosition Double -> ArcCentroid Double
forall a.
(FromInteger a, Ord a, TrigField a, ExpField a) =>
ArcPosition a -> ArcCentroid a
arcCentroid ArcPosition Double
p1
    arc1 :: Chart Double
arc1 = Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (PathStyle -> [PathInfo Double] -> Annotation
PathA (PathStyle
defaultPathStyle PathStyle -> (PathStyle -> PathStyle) -> PathStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> PathStyle -> Identity PathStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> PathStyle -> Identity PathStyle)
-> Colour -> PathStyle -> PathStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Colour
co PathStyle -> (PathStyle -> PathStyle) -> PathStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> PathStyle -> Identity PathStyle
forall a. IsLabel "borderColor" a => a
forall (x :: Symbol) a. IsLabel x a => a
#borderColor ((Colour -> Identity Colour) -> PathStyle -> Identity PathStyle)
-> Colour -> PathStyle -> PathStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double -> Colour -> Colour
setOpac Double
0.5 Colour
dark) ((PathInfo Double, Point Double) -> PathInfo Double
forall a b. (a, b) -> a
fst ((PathInfo Double, Point Double) -> PathInfo Double)
-> [(PathInfo Double, Point Double)] -> [PathInfo Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(PathInfo Double, Point Double)]
ps1)) (Point Double -> XY Double
forall a. Point a -> XY a
PointXY (Point Double -> XY Double)
-> ((PathInfo Double, Point Double) -> Point Double)
-> (PathInfo Double, Point Double)
-> XY Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (PathInfo Double, Point Double) -> Point Double
forall a b. (a, b) -> b
snd ((PathInfo Double, Point Double) -> XY Double)
-> [(PathInfo Double, Point Double)] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(PathInfo Double, Point Double)]
ps1)
    c1 :: Chart Double
c1 = Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (LineStyle -> Annotation
LineA (LineStyle -> Annotation) -> LineStyle -> Annotation
forall a b. (a -> b) -> a -> b
$ LineStyle
defaultLineStyle LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> LineStyle -> Identity LineStyle
forall a. IsLabel "width" a => a
forall (x :: Symbol) a. IsLabel x a => a
#width ((Double -> Identity Double) -> LineStyle -> Identity LineStyle)
-> Double -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.02 LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> LineStyle -> Identity LineStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> LineStyle -> Identity LineStyle)
-> Colour -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double -> Colour -> Colour
setOpac Double
0.2 Colour
dark) (Point Double -> XY Double
forall a. Point a -> XY a
PointXY (Point Double -> XY Double)
-> (Double -> Point Double) -> Double -> XY Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Point Double -> Point Double -> Double -> Double -> Point Double
forall b a.
(Direction b a, Affinity b a, TrigField a) =>
b -> b -> a -> a -> b
ellipse (Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
1.0 Double
1.0) (Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
1.0 Double
1.0) Double
0 (Double -> Point Double)
-> (Double -> Double) -> Double -> Point Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (\Double
x -> Double
0 Double -> Double -> Double
forall a. Additive a => a -> a -> a
+ Double
2 Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double
forall a. TrigField a => a
pi Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double
x Double -> Double -> Double
forall a. Divisive a => a -> a -> a
/ Double
100.0) (Double -> XY Double) -> [Double] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Double
0..Double
100])
    c2 :: Chart Double
c2 = Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (LineStyle -> Annotation
LineA (LineStyle -> Annotation) -> LineStyle -> Annotation
forall a b. (a -> b) -> a -> b
$ LineStyle
defaultLineStyle LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> LineStyle -> Identity LineStyle
forall a. IsLabel "width" a => a
forall (x :: Symbol) a. IsLabel x a => a
#width ((Double -> Identity Double) -> LineStyle -> Identity LineStyle)
-> Double -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.02 LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> LineStyle -> Identity LineStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> LineStyle -> Identity LineStyle)
-> Colour -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double -> Colour -> Colour
setOpac Double
0.2 Colour
dark) (Point Double -> XY Double
forall a. Point a -> XY a
PointXY (Point Double -> XY Double)
-> (Double -> Point Double) -> Double -> XY Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Point Double -> Point Double -> Double -> Double -> Point Double
forall b a.
(Direction b a, Affinity b a, TrigField a) =>
b -> b -> a -> a -> b
ellipse (Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
0.0 Double
0.0) (Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
1.0 Double
1.0) Double
0 (Double -> Point Double)
-> (Double -> Double) -> Double -> Point Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (\Double
x -> Double
0 Double -> Double -> Double
forall a. Additive a => a -> a -> a
+ Double
2 Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double
forall a. TrigField a => a
pi Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double
x Double -> Double -> Double
forall a. Divisive a => a -> a -> a
/ Double
100.0) (Double -> XY Double) -> [Double] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Double
0..Double
100])
    ell :: Chart Double
ell = Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (LineStyle -> Annotation
LineA (LineStyle -> Annotation) -> LineStyle -> Annotation
forall a b. (a -> b) -> a -> b
$ LineStyle
defaultLineStyle LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> LineStyle -> Identity LineStyle
forall a. IsLabel "width" a => a
forall (x :: Symbol) a. IsLabel x a => a
#width ((Double -> Identity Double) -> LineStyle -> Identity LineStyle)
-> Double -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.05 LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> LineStyle -> Identity LineStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> LineStyle -> Identity LineStyle)
-> Colour -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double -> Colour -> Colour
setOpac Double
0.5 Colour
co) (Point Double -> XY Double
forall a. Point a -> XY a
PointXY (Point Double -> XY Double)
-> (Double -> Point Double) -> Double -> XY Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Point Double -> Point Double -> Double -> Double -> Point Double
forall b a.
(Direction b a, Affinity b a, TrigField a) =>
b -> b -> a -> a -> b
ellipse Point Double
c' Point Double
r Double
phi' (Double -> Point Double)
-> (Double -> Double) -> Double -> Point Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (\Double
x -> Double
ang0 Double -> Double -> Double
forall a. Additive a => a -> a -> a
+ Double
angd Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double
x Double -> Double -> Double
forall a. Divisive a => a -> a -> a
/ Double
100.0) (Double -> XY Double) -> [Double] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Double
0..Double
100])

-- | quad example
--
-- ![quad example](other/quad.svg)
quadExample :: ChartSvg
quadExample :: ChartSvg
quadExample =
  ChartSvg
forall a. Monoid a => a
mempty ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
&
   #chartList .~ [path', curve, c0, bbox] &
   #hudOptions .~ defaultHudOptions &
   #svgOptions %~ ((#outerPad ?~ 0.05) . (#chartAspect .~ ChartAspect))
  where
    p :: QuadPosition Double
p@(QuadPosition Point Double
start Point Double
end Point Double
control) = Point Double -> Point Double -> Point Double -> QuadPosition Double
forall a. Point a -> Point a -> Point a -> QuadPosition a
QuadPosition (Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
0 Double
0) (Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
1 Double
1) (Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
2 Double
-1)
    ps :: [(PathInfo Double, Point Double)]
ps = QuadPosition Double -> [(PathInfo Double, Point Double)]
singletonQuad QuadPosition Double
p
    path' :: Chart Double
path' = Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (PathStyle -> [PathInfo Double] -> Annotation
PathA (PathStyle
defaultPathStyle PathStyle -> (PathStyle -> PathStyle) -> PathStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> PathStyle -> Identity PathStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> PathStyle -> Identity PathStyle)
-> Colour -> PathStyle -> PathStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double -> Colour -> Colour
setOpac Double
0.1 ([Colour]
palette1 [Colour] -> Int -> Colour
forall a. [a] -> Int -> a
List.!! Int
2) PathStyle -> (PathStyle -> PathStyle) -> PathStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> PathStyle -> Identity PathStyle
forall a. IsLabel "borderColor" a => a
forall (x :: Symbol) a. IsLabel x a => a
#borderColor ((Colour -> Identity Colour) -> PathStyle -> Identity PathStyle)
-> Colour -> PathStyle -> PathStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Colour
transparent) ((PathInfo Double, Point Double) -> PathInfo Double
forall a b. (a, b) -> a
fst ((PathInfo Double, Point Double) -> PathInfo Double)
-> [(PathInfo Double, Point Double)] -> [PathInfo Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(PathInfo Double, Point Double)]
ps)) (Point Double -> XY Double
forall a. Point a -> XY a
PointXY (Point Double -> XY Double)
-> ((PathInfo Double, Point Double) -> Point Double)
-> (PathInfo Double, Point Double)
-> XY Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (PathInfo Double, Point Double) -> Point Double
forall a b. (a, b) -> b
snd ((PathInfo Double, Point Double) -> XY Double)
-> [(PathInfo Double, Point Double)] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(PathInfo Double, Point Double)]
ps)
    curve :: Chart Double
curve = Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (LineStyle -> Annotation
LineA (LineStyle -> Annotation) -> LineStyle -> Annotation
forall a b. (a -> b) -> a -> b
$ LineStyle
defaultLineStyle LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> LineStyle -> Identity LineStyle
forall a. IsLabel "width" a => a
forall (x :: Symbol) a. IsLabel x a => a
#width ((Double -> Identity Double) -> LineStyle -> Identity LineStyle)
-> Double -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.002 LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> LineStyle -> Identity LineStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> LineStyle -> Identity LineStyle)
-> Colour -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ([Colour]
palette1 [Colour] -> Int -> Colour
forall a. [a] -> Int -> a
List.!! Int
1)) (Point Double -> XY Double
forall a. Point a -> XY a
PointXY (Point Double -> XY Double)
-> (Double -> Point Double) -> Double -> XY Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. QuadPosition Double -> Double -> Point Double
forall a.
(ExpField a, FromInteger a) =>
QuadPosition a -> a -> Point a
quadBezier QuadPosition Double
p (Double -> Point Double)
-> (Double -> Double) -> Double -> Point Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Double -> Double -> Double
forall a. Divisive a => a -> a -> a
/Double
100.0) (Double -> XY Double) -> [Double] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Double
0..Double
100])
    c0 :: Chart Double
c0 = Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (GlyphStyle -> Annotation
GlyphA GlyphStyle
defaultGlyphStyle) (Point Double -> XY Double
forall a. Point a -> XY a
PointXY (Point Double -> XY Double) -> [Point Double] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Point Double
start, Point Double
end, Point Double
control])
    bbox :: Chart Double
bbox = Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (RectStyle -> Annotation
RectA (RectStyle -> Annotation) -> RectStyle -> Annotation
forall a b. (a -> b) -> a -> b
$ RectStyle
defaultRectStyle RectStyle -> (RectStyle -> RectStyle) -> RectStyle
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> RectStyle -> Identity RectStyle
forall a. IsLabel "borderSize" a => a
forall (x :: Symbol) a. IsLabel x a => a
#borderSize ((Double -> Identity Double) -> RectStyle -> Identity RectStyle)
-> Double -> RectStyle -> RectStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.002 RectStyle -> (RectStyle -> RectStyle) -> RectStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> RectStyle -> Identity RectStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> RectStyle -> Identity RectStyle)
-> Colour -> RectStyle -> RectStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double -> Double -> Double -> Double -> Colour
Colour Double
0.4 Double
0.4 Double
0.8 Double
0.1 RectStyle -> (RectStyle -> RectStyle) -> RectStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> RectStyle -> Identity RectStyle
forall a. IsLabel "borderColor" a => a
forall (x :: Symbol) a. IsLabel x a => a
#borderColor ((Colour -> Identity Colour) -> RectStyle -> Identity RectStyle)
-> Colour -> RectStyle -> RectStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double -> Double -> Double -> Double -> Colour
Colour Double
0.5 Double
0.5 Double
0.5 Double
1) [Rect Double -> XY Double
forall a. Rect a -> XY a
RectXY (QuadPosition Double -> Rect Double
quadBox QuadPosition Double
p)]

-- | cubic example
--
-- ![cubic example](other/cubic.svg)
cubicExample :: ChartSvg
cubicExample :: ChartSvg
cubicExample =
  ChartSvg
forall a. Monoid a => a
mempty ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
&
   #chartList .~ [path', curve, c0, bbox] &
   #hudOptions .~ mempty &
   #svgOptions %~ ((#outerPad ?~ 0.02) . (#chartAspect .~ ChartAspect))
  where
    p :: CubicPosition Double
p@(CubicPosition Point Double
start Point Double
end Point Double
control1 Point Double
control2) = Point Double
-> Point Double
-> Point Double
-> Point Double
-> CubicPosition Double
forall a.
Point a -> Point a -> Point a -> Point a -> CubicPosition a
CubicPosition (Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
0 Double
0) (Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
1 Double
1) (Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
1 Double
0) (Double -> Double -> Point Double
forall a. a -> a -> Point a
Point Double
0 Double
1)
    ps :: [(PathInfo Double, Point Double)]
ps = CubicPosition Double -> [(PathInfo Double, Point Double)]
singletonCubic CubicPosition Double
p
    path' :: Chart Double
path' = Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (PathStyle -> [PathInfo Double] -> Annotation
PathA (PathStyle
defaultPathStyle PathStyle -> (PathStyle -> PathStyle) -> PathStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> PathStyle -> Identity PathStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> PathStyle -> Identity PathStyle)
-> Colour -> PathStyle -> PathStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double -> Colour -> Colour
setOpac Double
0.1 ([Colour]
palette1 [Colour] -> Int -> Colour
forall a. [a] -> Int -> a
List.!! Int
2) PathStyle -> (PathStyle -> PathStyle) -> PathStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> PathStyle -> Identity PathStyle
forall a. IsLabel "borderColor" a => a
forall (x :: Symbol) a. IsLabel x a => a
#borderColor ((Colour -> Identity Colour) -> PathStyle -> Identity PathStyle)
-> Colour -> PathStyle -> PathStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Colour
transparent) ((PathInfo Double, Point Double) -> PathInfo Double
forall a b. (a, b) -> a
fst ((PathInfo Double, Point Double) -> PathInfo Double)
-> [(PathInfo Double, Point Double)] -> [PathInfo Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(PathInfo Double, Point Double)]
ps)) (Point Double -> XY Double
forall a. Point a -> XY a
PointXY (Point Double -> XY Double)
-> ((PathInfo Double, Point Double) -> Point Double)
-> (PathInfo Double, Point Double)
-> XY Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (PathInfo Double, Point Double) -> Point Double
forall a b. (a, b) -> b
snd ((PathInfo Double, Point Double) -> XY Double)
-> [(PathInfo Double, Point Double)] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(PathInfo Double, Point Double)]
ps)
    curve :: Chart Double
curve = Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (LineStyle -> Annotation
LineA (LineStyle -> Annotation) -> LineStyle -> Annotation
forall a b. (a -> b) -> a -> b
$ LineStyle
defaultLineStyle LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> LineStyle -> Identity LineStyle
forall a. IsLabel "width" a => a
forall (x :: Symbol) a. IsLabel x a => a
#width ((Double -> Identity Double) -> LineStyle -> Identity LineStyle)
-> Double -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.002 LineStyle -> (LineStyle -> LineStyle) -> LineStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> LineStyle -> Identity LineStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> LineStyle -> Identity LineStyle)
-> Colour -> LineStyle -> LineStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ([Colour]
palette1 [Colour] -> Int -> Colour
forall a. [a] -> Int -> a
List.!! Int
1)) (Point Double -> XY Double
forall a. Point a -> XY a
PointXY (Point Double -> XY Double)
-> (Double -> Point Double) -> Double -> XY Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. CubicPosition Double -> Double -> Point Double
forall a.
(ExpField a, FromInteger a) =>
CubicPosition a -> a -> Point a
cubicBezier CubicPosition Double
p (Double -> Point Double)
-> (Double -> Double) -> Double -> Point Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Double -> Double -> Double
forall a. Divisive a => a -> a -> a
/Double
100.0) (Double -> XY Double) -> [Double] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Double
0..Double
100])
    c0 :: Chart Double
c0 = Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (GlyphStyle -> Annotation
GlyphA GlyphStyle
defaultGlyphStyle) (Point Double -> XY Double
forall a. Point a -> XY a
PointXY (Point Double -> XY Double) -> [Point Double] -> [XY Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Point Double
start, Point Double
end, Point Double
control1, Point Double
control2, CubicPosition Double -> Double -> Point Double
forall a.
(ExpField a, FromInteger a) =>
CubicPosition a -> a -> Point a
cubicBezier CubicPosition Double
p Double
0.8])
    bbox :: Chart Double
bbox = Annotation -> [XY Double] -> Chart Double
forall a. Annotation -> [XY a] -> Chart a
Chart (RectStyle -> Annotation
RectA (RectStyle -> Annotation) -> RectStyle -> Annotation
forall a b. (a -> b) -> a -> b
$ RectStyle
defaultRectStyle RectStyle -> (RectStyle -> RectStyle) -> RectStyle
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> RectStyle -> Identity RectStyle
forall a. IsLabel "borderSize" a => a
forall (x :: Symbol) a. IsLabel x a => a
#borderSize ((Double -> Identity Double) -> RectStyle -> Identity RectStyle)
-> Double -> RectStyle -> RectStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
0.002 RectStyle -> (RectStyle -> RectStyle) -> RectStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> RectStyle -> Identity RectStyle
forall a. IsLabel "color" a => a
forall (x :: Symbol) a. IsLabel x a => a
#color ((Colour -> Identity Colour) -> RectStyle -> Identity RectStyle)
-> Colour -> RectStyle -> RectStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double -> Double -> Double -> Double -> Colour
Colour Double
0.4 Double
0.4 Double
0.8 Double
0.1 RectStyle -> (RectStyle -> RectStyle) -> RectStyle
forall a b. a -> (a -> b) -> b
& (Colour -> Identity Colour) -> RectStyle -> Identity RectStyle
forall a. IsLabel "borderColor" a => a
forall (x :: Symbol) a. IsLabel x a => a
#borderColor ((Colour -> Identity Colour) -> RectStyle -> Identity RectStyle)
-> Colour -> RectStyle -> RectStyle
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double -> Double -> Double -> Double -> Colour
Colour Double
0.5 Double
0.5 Double
0.5 Double
1) [Rect Double -> XY Double
forall a. Rect a -> XY a
RectXY (CubicPosition Double -> Rect Double
cubicBox CubicPosition Double
p)]

-- | The common way to create a surface chart is usually a grid over a function.
--
-- ![surface example](other/surface.svg)
--
surfaceExample :: ChartSvg
surfaceExample :: ChartSvg
surfaceExample =
  ChartSvg
forall a. Monoid a => a
mempty ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
&
  #hudList .~ hs &
  #chartList .~ cs &
  #svgOptions .~ (defaultSvgOptions & #cssOptions .~ UseCssCrisp)
  where
    t :: Text
t = Text
"rosenbrock"
    grain :: Point Int
grain = Int -> Int -> Point Int
forall a. a -> a -> Point a
Point Int
20 Int
20
    r :: Rect Double
r = Rect Double
forall a. Multiplicative a => a
one
    f :: Point Double -> Double
f = (Double, Point Double) -> Double
forall a b. (a, b) -> a
fst ((Double, Point Double) -> Double)
-> (Point Double -> (Double, Point Double))
-> Point Double
-> Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Double -> Double)
-> (Point Double -> Point Double)
-> (Double, Point Double)
-> (Double, Point Double)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (Double
-1.0 Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
*) (Double
-1.0 Double -> Point Double -> Point Double
forall m a. MultiplicativeAction m a => a -> m -> m
.*) ((Double, Point Double) -> (Double, Point Double))
-> (Point Double -> (Double, Point Double))
-> Point Double
-> (Double, Point Double)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Double -> Double -> Point Double -> (Double, Point Double)
rosenbrock Double
1 Double
10
    ([Chart Double]
cs, [Hud Double]
hs) =
      (Point Double -> Double)
-> SurfaceOptions
-> SurfaceLegendOptions
-> ([Chart Double], [Hud Double])
surfacefl Point Double -> Double
f
      (SurfaceOptions
defaultSurfaceOptions SurfaceOptions
-> (SurfaceOptions -> SurfaceOptions) -> SurfaceOptions
forall a b. a -> (a -> b) -> b
&
       #soGrain .~ grain &
       #soRange .~ r &
       #soStyle . #surfaceColors .~ take 6 palette1)
      (Text -> SurfaceLegendOptions
defaultSurfaceLegendOptions Text
t SurfaceLegendOptions
-> (SurfaceLegendOptions -> SurfaceLegendOptions)
-> SurfaceLegendOptions
forall a b. a -> (a -> b) -> b
&
       #sloStyle . #surfaceColors .~ take 6 palette1)

-- | arrow example
--
-- Which happens to be the gradient of the surface example.
--
-- ![arrow example](other/arrow.svg)
arrowExample :: ChartSvg
arrowExample :: ChartSvg
arrowExample =
  ChartSvg
forall a. Monoid a => a
mempty ChartSvg -> (ChartSvg -> ChartSvg) -> ChartSvg
forall a b. a -> (a -> b) -> b
&
  #hudOptions .~ (defaultHudOptions & #hudAxes %~ fmap (#axisTick . #ltick .~ Nothing)) &
  #chartList .~ ((\p -> chart (tail . f $ p) (angle . f $ p) p) <$> ps) &
  #svgOptions .~ defaultSvgOptions
  where
    f :: Point Double -> Point Double
f = (Double, Point Double) -> Point Double
forall a b. (a, b) -> b
snd ((Double, Point Double) -> Point Double)
-> (Point Double -> (Double, Point Double))
-> Point Double
-> Point Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Double -> Double)
-> (Point Double -> Point Double)
-> (Double, Point Double)
-> (Double, Point Double)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (Double
-1.0 Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
*) (Double
-1.0 Double -> Point Double -> Point Double
forall m a. MultiplicativeAction m a => a -> m -> m
.*) ((Double, Point Double) -> (Double, Point Double))
-> (Point Double -> (Double, Point Double))
-> Point Double
-> (Double, Point Double)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Double -> Double -> Point Double -> (Double, Point Double)
rosenbrock Double
1 Double
10
    ps :: [Point Double]
ps = Pos -> Rect Double -> Grid (Rect Double) -> [Element (Rect Double)]
forall s. FieldSpace s => Pos -> s -> Grid s -> [Element s]
grid Pos
MidPos (Rect Double
forall a. Multiplicative a => a
one :: Rect Double) (Int -> Int -> Point Int
forall a. a -> a -> Point a
Point Int
10 Int
10 :: Point Int) :: [Point Double]
    arrow :: GlyphShape
arrow = Text -> GlyphShape
PathGlyph Text
"M -1 0 L 1 0 M 1 0 L 0.4 0.3 M 1 0 L 0.4 -0.3"
    gs :: Double -> Double -> GlyphStyle
gs Double
s Double
r' =
      GlyphStyle
defaultGlyphStyle GlyphStyle -> (GlyphStyle -> GlyphStyle) -> GlyphStyle
forall a b. a -> (a -> b) -> b
&
      #borderSize .~ 0.05 &
      #size .~ s &
      #borderColor .~ dark &
      #rotation .~ Just r' &
      #shape .~ arrow
    chart :: Double -> Double -> Point a -> Chart a
chart Double
s Double
r' Point a
p = Annotation -> [XY a] -> Chart a
forall a. Annotation -> [XY a] -> Chart a
Chart (GlyphStyle -> Annotation
GlyphA (Double -> Double -> GlyphStyle
gs Double
s Double
r')) [Point a -> XY a
forall a. Point a -> XY a
PointXY Point a
p]

    tail :: Point Double -> Double
    tail :: Point Double -> Double
tail = Double -> Double -> Double
forall a. Ord a => a -> a -> a
max Double
0.05 (Double -> Double)
-> (Point Double -> Double) -> Point Double -> Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Double -> Double -> Double
forall a. Ord a => a -> a -> a
min Double
0.02 (Double -> Double)
-> (Point Double -> Double) -> Point Double -> Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
*Double
0.01) (Double -> Double)
-> (Point Double -> Double) -> Point Double -> Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Double -> Double -> Double
forall a. Divisive a => a -> a -> a
/Double
avmag) (Double -> Double)
-> (Point Double -> Double) -> Point Double -> Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Point Double -> Double
forall a b. Norm a b => a -> b
norm

    avmag :: Double
avmag = [Double] -> Double
forall a (f :: * -> *). (Additive a, Foldable f) => f a -> a
sum (Point Double -> Double
forall a b. Norm a b => a -> b
norm (Point Double -> Double)
-> (Point Double -> Point Double) -> Point Double -> Double
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Point Double -> Point Double
f (Point Double -> Double) -> [Point Double] -> [Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Point Double]
ps) Double -> Double -> Double
forall a. Divisive a => a -> a -> a
/ Int -> Double
forall a b. FromIntegral a b => b -> a
fromIntegral ([Point Double] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Point Double]
ps)

-- | function for testing
--
-- > f(x,y) = (a-x)^2 + b * (y - x^2)^2
-- >        = a^2 - 2ax + x^2 + b * y^2 - b * 2 * y * x^2 + b * x ^ 4
-- > f'x = -2a + 2 * x - b * 4 * y * x + 4 * b * x ^ 3
-- > f'y = 2 * b * y - 2 * b * x^2
-- > f a b (Point x y) = (a^2 - 2ax + x^2 + b * y^2 - b * 2 * y * x^2 + b * x^4, Point (-2a + 2 * x - b * 4 * y * x + 4 * b * x ^ 3), 2 * b * y - 2 * b * x^2)
rosenbrock :: Double -> Double -> Point Double -> (Double, Point Double)
rosenbrock :: Double -> Double -> Point Double -> (Double, Point Double)
rosenbrock Double
a Double
b (Point Double
x Double
y) = (Double
aDouble -> Int -> Double
forall a. Divisive a => a -> Int -> a
^Int
2 Double -> Double -> Double
forall a. Subtractive a => a -> a -> a
- Double
2Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
*Double
aDouble -> Double -> Double
forall a. Multiplicative a => a -> a -> a
*Double
x Double -> Double -> Double
forall a. Additive a => a -> a -> a
+ Double
xDouble -> Int -> Double
forall a. Divisive a => a -> Int -> a
^Int
2 Double -> Double -> Double
forall a. Additive a => a -> a -> a
+ Double
b Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double
yDouble -> Int -> Double
forall a. Divisive a => a -> Int -> a
^Int
2 Double -> Double -> Double
forall a. Subtractive a => a -> a -> a
- Double
b Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double
2 Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double
y Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double
xDouble -> Int -> Double
forall a. Divisive a => a -> Int -> a
^Int
2 Double -> Double -> Double
forall a. Additive a => a -> a -> a
+ Double
b Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double
xDouble -> Int -> Double
forall a. Divisive a => a -> Int -> a
^Int
4, Double -> Double -> Point Double
forall a. a -> a -> Point a
Point (Double
-2Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
*Double
a Double -> Double -> Double
forall a. Additive a => a -> a -> a
+ Double
2 Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double
x Double -> Double -> Double
forall a. Subtractive a => a -> a -> a
- Double
b Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double
4 Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double
y Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double
x Double -> Double -> Double
forall a. Additive a => a -> a -> a
+ Double
4 Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double
b Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double
xDouble -> Int -> Double
forall a. Divisive a => a -> Int -> a
^Int
3) (Double
2 Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double
b Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double
y Double -> Double -> Double
forall a. Subtractive a => a -> a -> a
- Double
2 Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double
b Double -> Double -> Double
forall a. Multiplicative a => a -> a -> a
* Double
xDouble -> Int -> Double
forall a. Divisive a => a -> Int -> a
^Int
2))

-- | Run this to refresh haddock example SVGs.
writeAllExamples :: IO ()
writeAllExamples :: IO ()
writeAllExamples = do
  -- charts in Chart docs
  [Char] -> ChartSvg -> IO ()
writeChartSvg [Char]
"other/unit.svg" ChartSvg
unitExample
  [Char] -> ChartSvg -> IO ()
writeChartSvg [Char]
"other/rect.svg" ChartSvg
rectExample
  [Char] -> ChartSvg -> IO ()
writeChartSvg [Char]
"other/text.svg" ChartSvg
textExample
  [Char] -> ChartSvg -> IO ()
writeChartSvg [Char]
"other/glyphs.svg" ChartSvg
glyphsExample
  [Char] -> ChartSvg -> IO ()
writeChartSvg [Char]
"other/line.svg" ChartSvg
lineExample
  [Char] -> ChartSvg -> IO ()
writeChartSvg [Char]
"other/svgoptions.svg" ChartSvg
svgOptionsExample
  [Char] -> ChartSvg -> IO ()
writeChartSvg [Char]
"other/hudoptions.svg" ChartSvg
hudOptionsExample
  [Char] -> ChartSvg -> IO ()
writeChartSvg [Char]
"other/legend.svg" ChartSvg
legendExample
  -- charts in Chart.Bar docs
  [Char] -> ChartSvg -> IO ()
writeChartSvg [Char]
"other/bar.svg" ChartSvg
barExample
  -- charts in Chart.Surface docs
  [Char] -> ChartSvg -> IO ()
writeChartSvg [Char]
"other/surface.svg" ChartSvg
surfaceExample
  -- extra Charts
  [Char] -> ChartSvg -> IO ()
writeChartSvg [Char]
"other/wave.svg" ChartSvg
waveExample
  [Char] -> ChartSvg -> IO ()
writeChartSvg [Char]
"other/lglyph.svg" ChartSvg
lglyphExample
  [Char] -> ChartSvg -> IO ()
writeChartSvg [Char]
"other/glines.svg" ChartSvg
glinesExample
  [Char] -> ChartSvg -> IO ()
writeChartSvg [Char]
"other/compound.svg" ChartSvg
compoundExample
  [Char] -> ChartSvg -> IO ()
writeChartSvg [Char]
"other/textlocal.svg" ChartSvg
textLocalExample
  [Char] -> ChartSvg -> IO ()
writeChartSvg [Char]
"other/label.svg" ChartSvg
labelExample
  [Char] -> ChartSvg -> IO ()
writeChartSvg [Char]
"other/venn.svg" ChartSvg
vennExample
  [Char] -> ChartSvg -> IO ()
writeChartSvg [Char]
"other/path.svg" ChartSvg
pathExample
  [Char] -> ChartSvg -> IO ()
writeChartSvg [Char]
"other/arc.svg" ChartSvg
arcExample
  [Char] -> ChartSvg -> IO ()
writeChartSvg [Char]
"other/arcflags.svg" ChartSvg
arcFlagsExample
  [Char] -> ChartSvg -> IO ()
writeChartSvg [Char]
"other/ellipse.svg" ChartSvg
ellipseExample
  [Char] -> ChartSvg -> IO ()
writeChartSvg [Char]
"other/quad.svg" ChartSvg
quadExample
  [Char] -> ChartSvg -> IO ()
writeChartSvg [Char]
"other/cubic.svg" ChartSvg
cubicExample
  [Char] -> ChartSvg -> IO ()
writeChartSvg [Char]
"other/arrow.svg" ChartSvg
arrowExample

  Text -> IO ()
forall a (m :: * -> *). (Print a, MonadIO m) => a -> m ()
putStrLn (Text
"ok" :: Text)