{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE OverloadedStrings #-}
module Chart.Surface
( SurfaceData (..),
SurfaceOptions (..),
defaultSurfaceOptions,
SurfaceStyle (..),
defaultSurfaceStyle,
mkSurfaceData,
surfaces,
surfacef,
SurfaceLegendOptions (..),
defaultSurfaceLegendOptions,
surfaceLegendAxisOptions,
gridReferenceChart,
addSurfaceLegend,
)
where
import Chart.Data
import Chart.Hud
import Chart.Primitive
import Chart.Style
import Data.Bifunctor
import Data.Bool
import Data.Colour
import Data.Foldable
import Data.FormatN
import Data.Maybe
import GHC.Generics
import NumHask.Space
import Optics.Core
import Prelude
data SurfaceOptions = SurfaceOptions
{
SurfaceOptions -> SurfaceStyle
soStyle :: SurfaceStyle,
SurfaceOptions -> Point Int
soGrain :: Point Int,
SurfaceOptions -> Rect Double
soRange :: Rect Double
}
deriving (Int -> SurfaceOptions -> ShowS
[SurfaceOptions] -> ShowS
SurfaceOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SurfaceOptions] -> ShowS
$cshowList :: [SurfaceOptions] -> ShowS
show :: SurfaceOptions -> String
$cshow :: SurfaceOptions -> String
showsPrec :: Int -> SurfaceOptions -> ShowS
$cshowsPrec :: Int -> SurfaceOptions -> ShowS
Show, SurfaceOptions -> SurfaceOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SurfaceOptions -> SurfaceOptions -> Bool
$c/= :: SurfaceOptions -> SurfaceOptions -> Bool
== :: SurfaceOptions -> SurfaceOptions -> Bool
$c== :: SurfaceOptions -> SurfaceOptions -> Bool
Eq, forall x. Rep SurfaceOptions x -> SurfaceOptions
forall x. SurfaceOptions -> Rep SurfaceOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SurfaceOptions x -> SurfaceOptions
$cfrom :: forall x. SurfaceOptions -> Rep SurfaceOptions x
Generic)
defaultSurfaceOptions :: SurfaceOptions
defaultSurfaceOptions :: SurfaceOptions
defaultSurfaceOptions =
SurfaceStyle -> Point Int -> Rect Double -> SurfaceOptions
SurfaceOptions SurfaceStyle
defaultSurfaceStyle (forall a. a -> a -> Point a
Point Int
10 Int
10) forall a. Multiplicative a => a
one
data SurfaceStyle = SurfaceStyle
{
SurfaceStyle -> [Colour]
surfaceColors :: [Colour],
SurfaceStyle -> Style
surfaceRectStyle :: Style
}
deriving (Int -> SurfaceStyle -> ShowS
[SurfaceStyle] -> ShowS
SurfaceStyle -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SurfaceStyle] -> ShowS
$cshowList :: [SurfaceStyle] -> ShowS
show :: SurfaceStyle -> String
$cshow :: SurfaceStyle -> String
showsPrec :: Int -> SurfaceStyle -> ShowS
$cshowsPrec :: Int -> SurfaceStyle -> ShowS
Show, SurfaceStyle -> SurfaceStyle -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SurfaceStyle -> SurfaceStyle -> Bool
$c/= :: SurfaceStyle -> SurfaceStyle -> Bool
== :: SurfaceStyle -> SurfaceStyle -> Bool
$c== :: SurfaceStyle -> SurfaceStyle -> Bool
Eq, forall x. Rep SurfaceStyle x -> SurfaceStyle
forall x. SurfaceStyle -> Rep SurfaceStyle x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SurfaceStyle x -> SurfaceStyle
$cfrom :: forall x. SurfaceStyle -> Rep SurfaceStyle x
Generic)
defaultSurfaceStyle :: SurfaceStyle
defaultSurfaceStyle :: SurfaceStyle
defaultSurfaceStyle =
[Colour] -> Style -> SurfaceStyle
SurfaceStyle (Int -> Colour
palette forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Int
0 .. Int
1]) (Colour -> Style
blob Colour
dark)
data SurfaceData = SurfaceData
{
SurfaceData -> Rect Double
surfaceRect :: Rect Double,
SurfaceData -> Colour
surfaceColor :: Colour
}
deriving (Int -> SurfaceData -> ShowS
[SurfaceData] -> ShowS
SurfaceData -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SurfaceData] -> ShowS
$cshowList :: [SurfaceData] -> ShowS
show :: SurfaceData -> String
$cshow :: SurfaceData -> String
showsPrec :: Int -> SurfaceData -> ShowS
$cshowsPrec :: Int -> SurfaceData -> ShowS
Show, SurfaceData -> SurfaceData -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SurfaceData -> SurfaceData -> Bool
$c/= :: SurfaceData -> SurfaceData -> Bool
== :: SurfaceData -> SurfaceData -> Bool
$c== :: SurfaceData -> SurfaceData -> Bool
Eq, forall x. Rep SurfaceData x -> SurfaceData
forall x. SurfaceData -> Rep SurfaceData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SurfaceData x -> SurfaceData
$cfrom :: forall x. SurfaceData -> Rep SurfaceData x
Generic)
surfaces :: Style -> [SurfaceData] -> [Chart]
surfaces :: Style -> [SurfaceData] -> [Chart]
surfaces Style
rs [SurfaceData]
ps =
( \(SurfaceData Rect Double
r Colour
c) ->
Style -> ChartData -> Chart
Chart
(Style
rs forall a b. a -> (a -> b) -> b
& forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
set forall a. IsLabel "color" a => a
#color Colour
c)
([Rect Double] -> ChartData
RectData [Rect Double
r])
)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [SurfaceData]
ps
mkSurfaceData ::
(Point Double -> Double) ->
Rect Double ->
Grid (Rect Double) ->
[Colour] ->
([SurfaceData], Range Double)
mkSurfaceData :: (Point Double -> Double)
-> Rect Double
-> Grid (Rect Double)
-> [Colour]
-> ([SurfaceData], Range Double)
mkSurfaceData Point Double -> Double
f Rect Double
r Grid (Rect Double)
g [Colour]
cs = (forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Rect Double -> Colour -> SurfaceData
SurfaceData [Rect Double]
rects (forall a b c. (a -> b -> c) -> b -> a -> c
flip Double -> [Colour] -> Colour
mixes [Colour]
cs forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Double]
proj), Range Double
rx)
where
ps :: [(Rect Double, Double)]
ps = forall b.
(Point Double -> b)
-> Rect Double -> Grid (Rect Double) -> [(Rect Double, b)]
gridF Point Double -> Double
f Rect Double
r Grid (Rect Double)
g
rects :: [Rect Double]
rects = forall a b. (a, b) -> a
fst forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Rect Double, Double)]
ps
vs :: [Double]
vs = forall a b. (a, b) -> b
snd forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Rect Double, Double)]
ps
rx :: Range Double
rx = forall s (f :: * -> *).
(Space s, Traversable f) =>
f (Element s) -> s
unsafeSpace1 [Double]
vs :: Range Double
proj :: [Double]
proj = forall s.
(Space s, Field (Element s)) =>
s -> s -> Element s -> Element s
project Range Double
rx (forall a. a -> a -> Range a
Range Double
0 Double
1) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Double]
vs
surfacef :: (Point Double -> Double) -> SurfaceOptions -> ([Chart], Range Double)
surfacef :: (Point Double -> Double)
-> SurfaceOptions -> ([Chart], Range Double)
surfacef Point Double -> Double
f SurfaceOptions
cfg =
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (Style -> [SurfaceData] -> [Chart]
surfaces (forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view (forall a. IsLabel "soStyle" a => a
#soStyle forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall a. IsLabel "surfaceRectStyle" a => a
#surfaceRectStyle) SurfaceOptions
cfg)) forall a b. (a -> b) -> a -> b
$
(Point Double -> Double)
-> Rect Double
-> Grid (Rect Double)
-> [Colour]
-> ([SurfaceData], Range Double)
mkSurfaceData
Point Double -> Double
f
(forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view forall a. IsLabel "soRange" a => a
#soRange SurfaceOptions
cfg)
(forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view forall a. IsLabel "soGrain" a => a
#soGrain SurfaceOptions
cfg)
(forall (t :: * -> *) a. Foldable t => t a -> [a]
toList forall a b. (a -> b) -> a -> b
$ forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view (forall a. IsLabel "soStyle" a => a
#soStyle forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall a. IsLabel "surfaceColors" a => a
#surfaceColors) SurfaceOptions
cfg)
data SurfaceLegendOptions = SurfaceLegendOptions
{ SurfaceLegendOptions -> AxisOptions
sloAxisOptions :: AxisOptions,
SurfaceLegendOptions -> Double
sloWidth :: Double,
SurfaceLegendOptions -> Int
sloResolution :: Int,
SurfaceLegendOptions -> Range Double
sloDataRange :: Range Double,
SurfaceLegendOptions -> Rect Double
sloRect :: Rect Double,
SurfaceLegendOptions -> SurfaceStyle
sloSurfaceStyle :: SurfaceStyle
}
deriving (SurfaceLegendOptions -> SurfaceLegendOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SurfaceLegendOptions -> SurfaceLegendOptions -> Bool
$c/= :: SurfaceLegendOptions -> SurfaceLegendOptions -> Bool
== :: SurfaceLegendOptions -> SurfaceLegendOptions -> Bool
$c== :: SurfaceLegendOptions -> SurfaceLegendOptions -> Bool
Eq, Int -> SurfaceLegendOptions -> ShowS
[SurfaceLegendOptions] -> ShowS
SurfaceLegendOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SurfaceLegendOptions] -> ShowS
$cshowList :: [SurfaceLegendOptions] -> ShowS
show :: SurfaceLegendOptions -> String
$cshow :: SurfaceLegendOptions -> String
showsPrec :: Int -> SurfaceLegendOptions -> ShowS
$cshowsPrec :: Int -> SurfaceLegendOptions -> ShowS
Show, forall x. Rep SurfaceLegendOptions x -> SurfaceLegendOptions
forall x. SurfaceLegendOptions -> Rep SurfaceLegendOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SurfaceLegendOptions x -> SurfaceLegendOptions
$cfrom :: forall x. SurfaceLegendOptions -> Rep SurfaceLegendOptions x
Generic)
surfaceLegendAxisOptions :: AxisOptions
surfaceLegendAxisOptions :: AxisOptions
surfaceLegendAxisOptions =
Maybe AxisBar -> Maybe Adjustments -> Ticks -> Place -> AxisOptions
AxisOptions
forall a. Maybe a
Nothing
forall a. Maybe a
Nothing
( Tick
-> Maybe TickStyle -> Maybe TickStyle -> Maybe TickStyle -> Ticks
Ticks
(FormatN -> Int -> TickExtend -> Tick
TickRound (FStyle -> Maybe Int -> Int -> Bool -> Bool -> FormatN
FormatN FStyle
FSPrec (forall a. a -> Maybe a
Just Int
3) Int
4 Bool
True Bool
True) Int
4 TickExtend
NoTickExtend)
(forall a. a -> Maybe a
Just TickStyle
defaultGlyphTickStyleY)
(forall a. a -> Maybe a
Just (TickStyle
defaultTextTick forall a b. a -> (a -> b) -> b
& forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
set forall a. IsLabel "buffer" a => a
#buffer Double
0.05))
forall a. Maybe a
Nothing
)
Place
PlaceRight
defaultSurfaceLegendOptions :: SurfaceLegendOptions
defaultSurfaceLegendOptions :: SurfaceLegendOptions
defaultSurfaceLegendOptions =
AxisOptions
-> Double
-> Int
-> Range Double
-> Rect Double
-> SurfaceStyle
-> SurfaceLegendOptions
SurfaceLegendOptions AxisOptions
surfaceLegendAxisOptions Double
0.2 Int
100 forall a. Multiplicative a => a
one (forall a. a -> a -> a -> a -> Rect a
Rect Double
0.7 Double
0.9 Double
0 Double
0.5) SurfaceStyle
defaultSurfaceStyle
gridReferenceChart :: SurfaceLegendOptions -> ChartTree
gridReferenceChart :: SurfaceLegendOptions -> ChartTree
gridReferenceChart SurfaceLegendOptions
slo =
Text -> [Chart] -> ChartTree
named Text
"grid reference" forall a b. (a -> b) -> a -> b
$
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith
(\Rect Double
r Colour
c -> Style -> ChartData -> Chart
Chart (Colour -> Style
blob Colour
c) ([Rect Double] -> ChartData
RectData [Rect Double
r]))
(Range Double -> Rect Double
gridf forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Range Double]
spaceGrid)
[Colour]
colorGrid
where
spaceGrid :: [Range Double]
spaceGrid = forall s. FieldSpace s => s -> Grid s -> [s]
gridSpace (forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view forall a. IsLabel "sloDataRange" a => a
#sloDataRange SurfaceLegendOptions
slo) (forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view forall a. IsLabel "sloResolution" a => a
#sloResolution SurfaceLegendOptions
slo)
gridf :: Range Double -> Rect Double
gridf =
forall a. a -> a -> Bool -> a
bool
(\Range Double
yr -> forall a. Range a -> Range a -> Rect a
Ranges (forall a. a -> a -> Range a
Range Double
0 (forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view forall a. IsLabel "sloWidth" a => a
#sloWidth SurfaceLegendOptions
slo)) Range Double
yr)
(\Range Double
xr -> forall a. Range a -> Range a -> Rect a
Ranges Range Double
xr (forall a. a -> a -> Range a
Range Double
0 (forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view forall a. IsLabel "sloWidth" a => a
#sloWidth SurfaceLegendOptions
slo)))
(SurfaceLegendOptions -> Bool
isHori SurfaceLegendOptions
slo)
colorGrid :: [Colour]
colorGrid =
(\Double
x -> Double -> [Colour] -> Colour
mixes Double
x (forall (t :: * -> *) a. Foldable t => t a -> [a]
toList forall a b. (a -> b) -> a -> b
$ forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view (forall a. IsLabel "sloSurfaceStyle" a => a
#sloSurfaceStyle forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall a. IsLabel "surfaceColors" a => a
#surfaceColors) SurfaceLegendOptions
slo))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s. FieldSpace s => Pos -> s -> Grid s -> [Element s]
grid Pos
MidPos (forall a. a -> a -> Range a
Range Double
0 Double
1) (forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view forall a. IsLabel "sloResolution" a => a
#sloResolution SurfaceLegendOptions
slo)
isHori :: SurfaceLegendOptions -> Bool
isHori :: SurfaceLegendOptions -> Bool
isHori SurfaceLegendOptions
slo =
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view (forall a. IsLabel "sloAxisOptions" a => a
#sloAxisOptions forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall a. IsLabel "place" a => a
#place) SurfaceLegendOptions
slo forall a. Eq a => a -> a -> Bool
== Place
PlaceBottom
Bool -> Bool -> Bool
|| forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view (forall a. IsLabel "sloAxisOptions" a => a
#sloAxisOptions forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% forall a. IsLabel "place" a => a
#place) SurfaceLegendOptions
slo forall a. Eq a => a -> a -> Bool
== Place
PlaceTop
addSurfaceLegend :: SurfaceLegendOptions -> ChartTree -> ChartTree
addSurfaceLegend :: SurfaceLegendOptions -> ChartTree -> ChartTree
addSurfaceLegend SurfaceLegendOptions
slo ChartTree
ct = ChartTree
ctBoth
where
grc :: ChartTree
grc = SurfaceLegendOptions -> ChartTree
gridReferenceChart SurfaceLegendOptions
slo
hoLegend :: HudOptions
hoLegend = (forall a. Monoid a => a
mempty :: HudOptions) forall a b. a -> (a -> b) -> b
& forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
set forall a. IsLabel "axes" a => a
#axes [forall a. Double -> a -> Priority a
Priority Double
1 (forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view forall a. IsLabel "sloAxisOptions" a => a
#sloAxisOptions SurfaceLegendOptions
slo)]
grcLegend :: ChartTree
grcLegend = ChartAspect -> HudOptions -> ChartTree -> ChartTree
addHud (Double -> ChartAspect
FixedAspect (forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view forall a. IsLabel "sloWidth" a => a
#sloWidth SurfaceLegendOptions
slo)) HudOptions
hoLegend ChartTree
grc
ctbox :: Rect Double
ctbox = forall a. a -> Maybe a -> a
fromMaybe forall a. Multiplicative a => a
one (forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view Lens' ChartTree (Maybe (Rect Double))
styleBox' ChartTree
ct)
legbox :: Rect Double
legbox = Rect Double -> Rect Double -> Rect Double -> Rect Double
projectOnR Rect Double
ctbox forall a. Multiplicative a => a
one (forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view forall a. IsLabel "sloRect" a => a
#sloRect SurfaceLegendOptions
slo)
ctBoth :: ChartTree
ctBoth = forall a. Monoid a => [a] -> a
mconcat [Rect Double -> ChartTree -> ChartTree
projectChartTree Rect Double
legbox ChartTree
grcLegend, ChartTree
ct]