{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE OverloadedStrings #-}
module Chart.Compound
( runHudCompoundWith,
addHudCompound,
compoundMerge,
writeChartOptionsCompound,
encodeChartOptionsCompound,
markupChartOptionsCompound,
)
where
import Chart.Hud
import Chart.Markup
import Chart.Primitive
import Chart.Style
import Data.Bool
import Data.ByteString.Char8 qualified as C
import Data.Foldable
import Data.List qualified as List
import Data.Maybe
import MarkupParse
import Optics.Core
import Prelude
writeChartOptionsCompound :: FilePath -> [ChartOptions] -> IO ()
writeChartOptionsCompound :: FilePath -> [ChartOptions] -> IO ()
writeChartOptionsCompound FilePath
fp [ChartOptions]
cs = FilePath -> ByteString -> IO ()
C.writeFile FilePath
fp ([ChartOptions] -> ByteString
encodeChartOptionsCompound [ChartOptions]
cs)
encodeChartOptionsCompound :: [ChartOptions] -> C.ByteString
encodeChartOptionsCompound :: [ChartOptions] -> ByteString
encodeChartOptionsCompound [] = ByteString
forall a. Monoid a => a
mempty
encodeChartOptionsCompound cs :: [ChartOptions]
cs@(ChartOptions
c0 : [ChartOptions]
_) =
RenderStyle -> Standard -> Markup -> ByteString
markdown_ (Optic' A_Lens NoIx ChartOptions RenderStyle
-> ChartOptions -> RenderStyle
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view (Optic' A_Lens NoIx ChartOptions MarkupOptions
#markupOptions Optic' A_Lens NoIx ChartOptions MarkupOptions
-> Optic
A_Lens NoIx MarkupOptions MarkupOptions RenderStyle RenderStyle
-> Optic' A_Lens NoIx ChartOptions RenderStyle
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
% Optic
A_Lens NoIx MarkupOptions MarkupOptions RenderStyle RenderStyle
#renderStyle) ChartOptions
c0) Standard
Xml ([ChartOptions] -> Markup
markupChartOptionsCompound [ChartOptions]
cs)
markupChartOptionsCompound :: [ChartOptions] -> Markup
markupChartOptionsCompound :: [ChartOptions] -> Markup
markupChartOptionsCompound [] = Markup
forall a. Monoid a => a
mempty
markupChartOptionsCompound cs :: [ChartOptions]
cs@(ChartOptions
co0 : [ChartOptions]
_) =
Maybe Double -> Rect Double -> Markup -> Markup
header
(Optic' A_Lens NoIx ChartOptions (Maybe Double)
-> ChartOptions -> Maybe Double
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view (Optic' A_Lens NoIx ChartOptions MarkupOptions
#markupOptions Optic' A_Lens NoIx ChartOptions MarkupOptions
-> Optic
A_Lens
NoIx
MarkupOptions
MarkupOptions
(Maybe Double)
(Maybe Double)
-> Optic' A_Lens NoIx ChartOptions (Maybe Double)
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
% Optic
A_Lens
NoIx
MarkupOptions
MarkupOptions
(Maybe Double)
(Maybe Double)
#markupHeight) ChartOptions
co0)
Rect Double
viewbox
( CssOptions -> Markup
markupCssOptions (Optic' A_Lens NoIx ChartOptions CssOptions
-> ChartOptions -> CssOptions
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view (Optic' A_Lens NoIx ChartOptions MarkupOptions
#markupOptions Optic' A_Lens NoIx ChartOptions MarkupOptions
-> Optic
A_Lens NoIx MarkupOptions MarkupOptions CssOptions CssOptions
-> Optic' A_Lens NoIx ChartOptions CssOptions
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
% Optic A_Lens NoIx MarkupOptions MarkupOptions CssOptions CssOptions
#cssOptions) ChartOptions
co0)
Markup -> Markup -> Markup
forall a. Semigroup a => a -> a -> a
<> ChartTree -> Markup
markupChartTree ChartTree
ctFinal
)
where
viewbox :: Rect Double
viewbox = Optic' A_Getter NoIx ChartTree (Rect Double)
-> ChartTree -> Rect Double
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view Optic' A_Getter NoIx ChartTree (Rect Double)
safeStyleBox' ChartTree
ctFinal
ctFinal :: ChartTree
ctFinal =
ChartAspect -> [(HudOptions, ChartTree)] -> ChartTree
projectChartCompoundWith
(Optic' A_Lens NoIx ChartOptions ChartAspect
-> ChartOptions -> ChartAspect
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view (Optic' A_Lens NoIx ChartOptions MarkupOptions
#markupOptions Optic' A_Lens NoIx ChartOptions MarkupOptions
-> Optic
A_Lens NoIx MarkupOptions MarkupOptions ChartAspect ChartAspect
-> Optic' A_Lens NoIx ChartOptions ChartAspect
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
% Optic
A_Lens NoIx MarkupOptions MarkupOptions ChartAspect ChartAspect
#chartAspect) ChartOptions
co0)
([HudOptions] -> [ChartTree] -> [(HudOptions, ChartTree)]
forall a b. [a] -> [b] -> [(a, b)]
zip (Optic' A_Lens NoIx ChartOptions HudOptions
-> ChartOptions -> HudOptions
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view Optic' A_Lens NoIx ChartOptions HudOptions
#hudOptions (ChartOptions -> HudOptions) -> [ChartOptions] -> [HudOptions]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ChartOptions]
cs) (Optic' A_Lens NoIx ChartOptions ChartTree
-> ChartOptions -> ChartTree
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view Optic' A_Lens NoIx ChartOptions ChartTree
#chartTree (ChartOptions -> ChartTree) -> [ChartOptions] -> [ChartTree]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ChartOptions]
cs))
projectChartCompoundWith :: ChartAspect -> [(HudOptions, ChartTree)] -> ChartTree
projectChartCompoundWith :: ChartAspect -> [(HudOptions, ChartTree)] -> ChartTree
projectChartCompoundWith ChartAspect
asp [(HudOptions, ChartTree)]
css = ChartTree
ctFinal
where
csAndHud :: ChartTree
csAndHud = ChartAspect -> [(HudOptions, ChartTree)] -> ChartTree
addHudCompound ChartAspect
asp [(HudOptions, ChartTree)]
css
viewbox :: Rect Double
viewbox = ChartAspect -> Maybe ChartTree -> Rect Double
finalCanvas ChartAspect
asp (ChartTree -> Maybe ChartTree
forall a. a -> Maybe a
Just ChartTree
csAndHud)
ctFinal :: ChartTree
ctFinal = Optic
A_Lens
NoIx
ChartTree
ChartTree
(Maybe (Rect Double))
(Maybe (Rect Double))
-> Maybe (Rect Double) -> ChartTree -> ChartTree
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
set Optic
A_Lens
NoIx
ChartTree
ChartTree
(Maybe (Rect Double))
(Maybe (Rect Double))
styleBox' (Rect Double -> Maybe (Rect Double)
forall a. a -> Maybe a
Just Rect Double
viewbox) ChartTree
csAndHud
compoundMerge :: [ChartOptions] -> ChartOptions
compoundMerge :: [ChartOptions] -> ChartOptions
compoundMerge [] = ChartOptions
forall a. Monoid a => a
mempty
compoundMerge cs :: [ChartOptions]
cs@(ChartOptions
c0 : [ChartOptions]
_) =
MarkupOptions -> HudOptions -> ChartTree -> ChartOptions
ChartOptions
(Optic' A_Lens NoIx ChartOptions MarkupOptions
-> ChartOptions -> MarkupOptions
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view Optic' A_Lens NoIx ChartOptions MarkupOptions
#markupOptions ChartOptions
c0)
HudOptions
forall a. Monoid a => a
mempty
(ChartAspect -> [(HudOptions, ChartTree)] -> ChartTree
addHudCompound (Optic' A_Lens NoIx ChartOptions ChartAspect
-> ChartOptions -> ChartAspect
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view (Optic' A_Lens NoIx ChartOptions MarkupOptions
#markupOptions Optic' A_Lens NoIx ChartOptions MarkupOptions
-> Optic
A_Lens NoIx MarkupOptions MarkupOptions ChartAspect ChartAspect
-> Optic' A_Lens NoIx ChartOptions ChartAspect
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
% Optic
A_Lens NoIx MarkupOptions MarkupOptions ChartAspect ChartAspect
#chartAspect) ChartOptions
c0) ([HudOptions] -> [ChartTree] -> [(HudOptions, ChartTree)]
forall a b. [a] -> [b] -> [(a, b)]
zip (Optic' A_Lens NoIx ChartOptions HudOptions
-> ChartOptions -> HudOptions
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view Optic' A_Lens NoIx ChartOptions HudOptions
#hudOptions (ChartOptions -> HudOptions) -> [ChartOptions] -> [HudOptions]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ChartOptions]
cs) (Optic' A_Lens NoIx ChartOptions ChartTree
-> ChartOptions -> ChartTree
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view Optic' A_Lens NoIx ChartOptions ChartTree
#chartTree (ChartOptions -> ChartTree) -> [ChartOptions] -> [ChartTree]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ChartOptions]
cs)))
addHudCompound :: ChartAspect -> [(HudOptions, ChartTree)] -> ChartTree
addHudCompound :: ChartAspect -> [(HudOptions, ChartTree)] -> ChartTree
addHudCompound ChartAspect
_ [] = ChartTree
forall a. Monoid a => a
mempty
addHudCompound ChartAspect
asp ts :: [(HudOptions, ChartTree)]
ts@((HudOptions
_, ChartTree
cs0) : [(HudOptions, ChartTree)]
_) =
Rect Double -> [(Rect Double, [Hud], ChartTree)] -> ChartTree
runHudCompoundWith
(ChartAspect -> Maybe ChartTree -> Rect Double
initialCanvas ChartAspect
asp (ChartTree -> Maybe ChartTree
forall a. a -> Maybe a
Just ChartTree
cs0))
([Rect Double]
-> [[Hud]] -> [ChartTree] -> [(Rect Double, [Hud], ChartTree)]
forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 [Rect Double]
dbs' [[Hud]]
hss [ChartTree]
css')
where
css :: [ChartTree]
css :: [ChartTree]
css = (HudOptions, ChartTree) -> ChartTree
forall a b. (a, b) -> b
snd ((HudOptions, ChartTree) -> ChartTree)
-> [(HudOptions, ChartTree)] -> [ChartTree]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(HudOptions, ChartTree)]
ts
hos :: [HudOptions]
hos = (HudOptions, ChartTree) -> HudOptions
forall a b. (a, b) -> a
fst ((HudOptions, ChartTree) -> HudOptions)
-> [(HudOptions, ChartTree)] -> [HudOptions]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(HudOptions, ChartTree)]
ts
dbs :: [Rect Double]
dbs = Optic' A_Getter NoIx ChartTree (Rect Double)
-> ChartTree -> Rect Double
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view Optic' A_Getter NoIx ChartTree (Rect Double)
safeBox' (ChartTree -> Rect Double) -> [ChartTree] -> [Rect Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ChartTree]
css
huds :: [(Maybe (Rect Double), [Hud])]
huds = (HudOptions -> Rect Double -> (Maybe (Rect Double), [Hud]))
-> [HudOptions] -> [Rect Double] -> [(Maybe (Rect Double), [Hud])]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith HudOptions -> Rect Double -> (Maybe (Rect Double), [Hud])
toHuds [HudOptions]
hos [Rect Double]
dbs
mdbs :: [Maybe (Rect Double)]
mdbs = (Maybe (Rect Double), [Hud]) -> Maybe (Rect Double)
forall a b. (a, b) -> a
fst ((Maybe (Rect Double), [Hud]) -> Maybe (Rect Double))
-> [(Maybe (Rect Double), [Hud])] -> [Maybe (Rect Double)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Maybe (Rect Double), [Hud])]
huds
hss :: [[Hud]]
hss = (Maybe (Rect Double), [Hud]) -> [Hud]
forall a b. (a, b) -> b
snd ((Maybe (Rect Double), [Hud]) -> [Hud])
-> [(Maybe (Rect Double), [Hud])] -> [[Hud]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Maybe (Rect Double), [Hud])]
huds
dbs' :: [Rect Double]
dbs' = (Rect Double -> Maybe (Rect Double) -> Rect Double)
-> [Rect Double] -> [Maybe (Rect Double)] -> [Rect Double]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Rect Double -> Maybe (Rect Double) -> Rect Double
forall a. a -> Maybe a -> a
fromMaybe [Rect Double]
dbs [Maybe (Rect Double)]
mdbs
css' :: [ChartTree]
css' :: [ChartTree]
css' = (ChartTree -> Maybe (Rect Double) -> Rect Double -> ChartTree)
-> [ChartTree]
-> [Maybe (Rect Double)]
-> [Rect Double]
-> [ChartTree]
forall a b c d. (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
zipWith3 (\ChartTree
cs Maybe (Rect Double)
mdb Rect Double
db -> ChartTree
cs ChartTree -> ChartTree -> ChartTree
forall a. Semigroup a => a -> a -> a
<> ChartTree
-> (Rect Double -> ChartTree) -> Maybe (Rect Double) -> ChartTree
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ChartTree
forall a. Monoid a => a
mempty (\Rect Double
r -> ChartTree -> ChartTree -> Bool -> ChartTree
forall a. a -> a -> Bool -> a
bool (Text -> [Chart] -> ChartTree
named Text
"datapadding" [Style -> [Rect Double] -> Chart
BlankChart Style
defaultStyle [Rect Double
r]]) ChartTree
forall a. Monoid a => a
mempty (Rect Double
r Rect Double -> Rect Double -> Bool
forall a. Eq a => a -> a -> Bool
== Rect Double
db)) Maybe (Rect Double)
mdb) [ChartTree]
css [Maybe (Rect Double)]
mdbs [Rect Double]
dbs
runHudCompoundWith ::
ChartBox ->
[(DataBox, [Hud], ChartTree)] ->
ChartTree
runHudCompoundWith :: Rect Double -> [(Rect Double, [Hud], ChartTree)] -> ChartTree
runHudCompoundWith Rect Double
cb [(Rect Double, [Hud], ChartTree)]
ts = ChartTree
hss
where
hss :: ChartTree
hss =
[(Rect Double, [Hud], ChartTree)]
ts
[(Rect Double, [Hud], ChartTree)]
-> ([(Rect Double, [Hud], ChartTree)] -> [[Hud]]) -> [[Hud]]
forall a b. a -> (a -> b) -> b
& ((Rect Double, [Hud], ChartTree) -> [Hud])
-> [(Rect Double, [Hud], ChartTree)] -> [[Hud]]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Rect Double
_, [Hud]
hs, ChartTree
_) -> [Hud]
hs)
[[Hud]] -> ([[Hud]] -> [Hud]) -> [Hud]
forall a b. a -> (a -> b) -> b
& [[Hud]] -> [Hud]
forall a. Monoid a => [a] -> a
mconcat
[Hud] -> ([Hud] -> [[Hud]]) -> [[Hud]]
forall a b. a -> (a -> b) -> b
& [Hud] -> [[Hud]]
prioritizeHuds
[[Hud]]
-> ([[Hud]] -> [[HudChart -> ChartTree]])
-> [[HudChart -> ChartTree]]
forall a b. a -> (a -> b) -> b
& ([Hud] -> [HudChart -> ChartTree])
-> [[Hud]] -> [[HudChart -> ChartTree]]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Hud -> HudChart -> ChartTree) -> [Hud] -> [HudChart -> ChartTree]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Optic' A_Lens NoIx Hud (HudChart -> ChartTree)
-> Hud -> HudChart -> ChartTree
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view (Optic
A_Lens
NoIx
Hud
Hud
(Priority (HudChart -> ChartTree))
(Priority (HudChart -> ChartTree))
#phud Optic
A_Lens
NoIx
Hud
Hud
(Priority (HudChart -> ChartTree))
(Priority (HudChart -> ChartTree))
-> Optic
A_Lens
NoIx
(Priority (HudChart -> ChartTree))
(Priority (HudChart -> ChartTree))
(HudChart -> ChartTree)
(HudChart -> ChartTree)
-> Optic' A_Lens NoIx Hud (HudChart -> ChartTree)
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
% Optic
A_Lens
NoIx
(Priority (HudChart -> ChartTree))
(Priority (HudChart -> ChartTree))
(HudChart -> ChartTree)
(HudChart -> ChartTree)
#item)))
[[HudChart -> ChartTree]]
-> ([[HudChart -> ChartTree]] -> HudChart) -> HudChart
forall a b. a -> (a -> b) -> b
& (HudChart -> [HudChart -> ChartTree] -> HudChart)
-> HudChart -> [[HudChart -> ChartTree]] -> HudChart
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\HudChart
x [HudChart -> ChartTree]
a -> [HudChart -> ChartTree] -> HudChart -> HudChart
makeHuds [HudChart -> ChartTree]
a HudChart
x) HudChart
hc0
HudChart -> (HudChart -> ChartTree) -> ChartTree
forall a b. a -> (a -> b) -> b
& HudChart -> ChartTree
fromHudChart
css :: ChartTree
css =
[(Rect Double, [Hud], ChartTree)]
ts
[(Rect Double, [Hud], ChartTree)]
-> ([(Rect Double, [Hud], ChartTree)] -> [ChartTree])
-> [ChartTree]
forall a b. a -> (a -> b) -> b
& ((Rect Double, [Hud], ChartTree) -> ChartTree)
-> [(Rect Double, [Hud], ChartTree)] -> [ChartTree]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Rect Double
db, [Hud]
_, ChartTree
ct) -> Optic A_Traversal NoIx ChartTree ChartTree Chart Chart
-> (Chart -> Chart) -> ChartTree -> ChartTree
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> (a -> b) -> s -> t
over Optic A_Traversal NoIx ChartTree ChartTree Chart Chart
chart' (Rect Double -> Rect Double -> Chart -> Chart
projectWith Rect Double
cb Rect Double
db) ChartTree
ct)
[ChartTree] -> ([ChartTree] -> ChartTree) -> ChartTree
forall a b. a -> (a -> b) -> b
& [ChartTree] -> ChartTree
forall a. Monoid a => [a] -> a
mconcat
hc0 :: HudChart
hc0 = ChartTree -> ChartTree -> HudChart
HudChart (ChartTree
css ChartTree -> (ChartTree -> ChartTree) -> ChartTree
forall a b. a -> (a -> b) -> b
& Optic
A_Lens
NoIx
ChartTree
ChartTree
(Maybe (Rect Double))
(Maybe (Rect Double))
-> Maybe (Rect Double) -> ChartTree -> ChartTree
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
set Optic
A_Lens
NoIx
ChartTree
ChartTree
(Maybe (Rect Double))
(Maybe (Rect Double))
styleBox' (Rect Double -> Maybe (Rect Double)
forall a. a -> Maybe a
Just Rect Double
cb)) ChartTree
forall a. Monoid a => a
mempty
prioritizeHuds :: [Hud] -> [[Hud]]
prioritizeHuds :: [Hud] -> [[Hud]]
prioritizeHuds [Hud]
hss =
[Hud]
hss
[Hud] -> ([Hud] -> [Hud]) -> [Hud]
forall a b. a -> (a -> b) -> b
& (Hud -> Double) -> [Hud] -> [Hud]
forall b a. Ord b => (a -> b) -> [a] -> [a]
List.sortOn (Optic' A_Lens NoIx Hud Double -> Hud -> Double
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view (Optic
A_Lens
NoIx
Hud
Hud
(Priority (HudChart -> ChartTree))
(Priority (HudChart -> ChartTree))
#phud Optic
A_Lens
NoIx
Hud
Hud
(Priority (HudChart -> ChartTree))
(Priority (HudChart -> ChartTree))
-> Optic
A_Lens
NoIx
(Priority (HudChart -> ChartTree))
(Priority (HudChart -> ChartTree))
Double
Double
-> Optic' A_Lens NoIx Hud Double
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
% Optic
A_Lens
NoIx
(Priority (HudChart -> ChartTree))
(Priority (HudChart -> ChartTree))
Double
Double
#priority))
[Hud] -> ([Hud] -> [[Hud]]) -> [[Hud]]
forall a b. a -> (a -> b) -> b
& (Hud -> Hud -> Bool) -> [Hud] -> [[Hud]]
forall a. (a -> a -> Bool) -> [a] -> [[a]]
List.groupBy (\Hud
a Hud
b -> Optic' A_Lens NoIx Hud Double -> Hud -> Double
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view (Optic
A_Lens
NoIx
Hud
Hud
(Priority (HudChart -> ChartTree))
(Priority (HudChart -> ChartTree))
#phud Optic
A_Lens
NoIx
Hud
Hud
(Priority (HudChart -> ChartTree))
(Priority (HudChart -> ChartTree))
-> Optic
A_Lens
NoIx
(Priority (HudChart -> ChartTree))
(Priority (HudChart -> ChartTree))
Double
Double
-> Optic' A_Lens NoIx Hud Double
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
% Optic
A_Lens
NoIx
(Priority (HudChart -> ChartTree))
(Priority (HudChart -> ChartTree))
Double
Double
#priority) Hud
a Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Optic' A_Lens NoIx Hud Double -> Hud -> Double
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view (Optic
A_Lens
NoIx
Hud
Hud
(Priority (HudChart -> ChartTree))
(Priority (HudChart -> ChartTree))
#phud Optic
A_Lens
NoIx
Hud
Hud
(Priority (HudChart -> ChartTree))
(Priority (HudChart -> ChartTree))
-> Optic
A_Lens
NoIx
(Priority (HudChart -> ChartTree))
(Priority (HudChart -> ChartTree))
Double
Double
-> Optic' A_Lens NoIx Hud Double
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
% Optic
A_Lens
NoIx
(Priority (HudChart -> ChartTree))
(Priority (HudChart -> ChartTree))
Double
Double
#priority) Hud
b)