{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}
module Plots.Axis.ColourBar
(
ColourBar
, HasColourBar (..)
, defColourBar
, gradientColourBar
, pathColourBar
, renderColourBar
, addColourBar
) where
import Data.Bool (bool)
import qualified Data.Foldable as F
import Diagrams.Prelude hiding (orient)
import Diagrams.TwoD.Text
import Plots.Axis.Grid
import Plots.Axis.Labels
import Plots.Axis.Ticks
import Plots.Style
import Plots.Types
import Plots.Util
import Geometry.TwoD.Transform
data ColourBar = ColourBar
{ cbPlacement :: Placement
, cbVisible :: Bool
, cbTicks :: MajorTicks V2
, cbMinorTicks :: MinorTicks V2
, cbGridLines :: MajorGridLines V2
, cbTickLabels :: TickLabels V2
, cbDraw :: ColourMap -> Diagram V2
, cbWidth :: Double
, cbLengthFun :: Double -> Double
, cbGap :: Double
, cbStyle :: Style V2 Double
}
type instance V ColourBar = V2
type instance N ColourBar = Double
defColourBar :: ColourBar
defColourBar = ColourBar
{ cbPlacement = rightMid
, cbVisible = False
, cbTicks = def
, cbMinorTicks = def & hidden .~ True
, cbGridLines = def
, cbTickLabels = def
, cbDraw = gradientColourBar
, cbWidth = 20
, cbLengthFun = id
, cbGap = 20
, cbStyle = mempty
}
class HasColourBar a where
colourBar :: Lens' a ColourBar
colourBarDraw :: Lens' a (ColourMap -> Diagram V2)
colourBarDraw = colourBar . lens cbDraw (\c a -> c {cbDraw = a})
colourBarWidth :: Lens' a Double
colourBarWidth = colourBar . lens cbWidth (\c a -> c {cbWidth = a})
colourBarLengthFunction :: Lens' a (Double -> Double)
colourBarLengthFunction = colourBar . lens cbLengthFun (\c a -> c {cbLengthFun = a})
colourBarGap :: Lens' a Double
colourBarGap = colourBar . lens cbGap (\c a -> c {cbGap = a})
colourBarStyle :: Lens' a (Style V2 Double)
colourBarStyle = colourBar . lens cbStyle (\c a -> c {cbStyle = a})
instance HasColourBar ColourBar where
colourBar = id
instance HasGap ColourBar where
gap = colourBarGap
instance HasPlacement ColourBar where
placement = lens cbPlacement (\c p -> c {cbPlacement = p})
instance HasOrientation ColourBar where
orientation = lens getter setter where
getter p
| north || south = Horizontal
| east || west = Vertical
| northEast = bool Horizontal Vertical (dx > dy)
| southEast = bool Horizontal Vertical (dx > -dy)
| southWest = bool Horizontal Vertical (dx < dy)
| northWest = bool Horizontal Vertical (dx < -dy)
| otherwise = error $ "internal error: get colourBar orientation: "
++ show (p ^. placement)
where
V2 x y = p ^. placementAt
V2 dx dy = p ^. gapDirection . _Dir
north = x < y && x > (-y)
east = x > y && x > (-y)
south = x > y && x < (-y)
west = x < y && x < (-y)
northEast = x == y && x > 0
southEast = x == (-y) && x > 0
southWest = x == y && x < 0
northWest = x == (-y) && x < 0
setter p o
| getter p == o = p
| otherwise = p & placementAt %~ flipX_Y
& placementAnchor %~ flipX_Y
& gapDirection ._Dir %~ flipX_Y
instance ApplyStyle ColourBar
instance HasStyle ColourBar where
style = colourBarStyle
instance Functor f => HasMajorTicks f ColourBar where
majorTicks = lens cbTicks (\c a -> c {cbTicks = a})
instance Functor f => HasMinorTicks f ColourBar where
minorTicks = lens cbMinorTicks (\c a -> c {cbMinorTicks = a})
instance Functor f => HasMajorGridLines f ColourBar where
majorGridLines = lens cbGridLines (\c a -> c {cbGridLines = a})
instance Functor f => HasTickLabels f ColourBar where
tickLabel = lens cbTickLabels (\c a -> c {cbTickLabels = a})
instance HasVisibility ColourBar where
visible = lens cbVisible (\c a -> c {cbVisible = a})
addColourBar
:: BoundingBox V2 Double
-> ColourBar
-> ColourMap
-> (Double,Double)
-> Diagram V2
addColourBar bb cbo@ColourBar {..} cm bnds
| cbVisible = placeAgainst bb cbPlacement cbGap cb
| otherwise = mempty
where
cb = renderColourBar cbo cm bnds l
l = cbLengthFun bbl
bbl = orient cbo bx by
V2 bx by = boxExtents bb
renderColourBar
:: ColourBar
-> ColourMap
-> (Double,Double)
-> Double
-> Diagram V2
renderColourBar cb@ColourBar {..} cm bnds@(lb,ub) l
| cbVisible = bar # xy id reflectY
# o id (reflectY . _reflectX_Y)
<> tLbs
| otherwise = mempty
where
o, xy :: a -> a -> a
o = orient cb
xy a b = if let V2 x y = cb^.placementAt in x > y
then a else b
w = cbWidth
f x = (x - (ub + lb)/2) / (ub - lb) * l
inRange x = x >= lb && x <= ub
bar = outline <> tks <> minorTks <> gLines <> colours
outline = rect l w # applyStyle (cbStyle & _fillTexture ?~ _AC ## transparent)
colours = cbDraw cm # centerXY # scaleX l # scaleY w
tickXs = view majorTicksFunction cbTicks bnds
tickXs' = filter inRange tickXs
tks
| cbTicks ^. hidden = mempty
| otherwise = F.foldMap (\x -> aTick # translate (V2 (f x) (-w/2))) tickXs'
aTick = someTick (cbTicks ^. majorTicksAlignment) (cbTicks ^. majorTicksLength)
minorTickXs = view minorTicksFunction cbMinorTicks tickXs bnds
minorTickXs' = filter inRange minorTickXs
minorTks
| cbMinorTicks ^. hidden = mempty
| otherwise = F.foldMap (\x -> aMinorTick # translate (V2 (f x) (-w/2))) minorTickXs'
# applyStyle (cbMinorTicks ^. minorTicksStyle)
aMinorTick = someTick (cbTicks ^. majorTicksAlignment) (cbTicks ^. majorTicksLength)
someTick tType d = case tType of
TickSpec (fromRational -> aa) (fromRational -> bb)
-> fromVertices [mkP2 0 (-d*bb), mkP2 0 (d*aa)]
AutoTick -> fromVertices [mkP2 0 (-d) , mkP2 0 d ]
gridXs = filter inRange $ view majorGridLinesFunction cbGridLines tickXs bnds
gLines
| cbGridLines ^. hidden = mempty
| otherwise = F.foldMap mkGridLine gridXs
# (stroke :: Path V2 Double -> Diagram V2)
# applyStyle (cbGridLines ^. majorGridLinesStyle)
mkGridLine x = fromVertices [mkP2 (f x) (-w/2), mkP2 (f x) (w/2)]
tickLabelXs = view tickLabelFunction cbTickLabels tickXs' bnds
tLbs
| cbTickLabels ^. hidden = mempty
| otherwise = F.foldMap drawTickLabel tickLabelXs
drawTickLabel (x,label) =
view tickLabelTextFunction cbTickLabels tAlign label
# translate v
# applyStyle (cbTickLabels ^. tickLabelStyle)
where v = V2 (f x) (- w/2 - view tickLabelGap cbTickLabels)
# xy id (_y %~ negate)
# o id ((_y %~ negate) . flipX_Y)
tAlign = o (xy (BoxAlignedText 0.5 1) (BoxAlignedText 0.5 0))
(xy (BoxAlignedText 0 0.5) (BoxAlignedText 1 0.5))
gradientColourBar :: ColourMap -> Diagram V2
gradientColourBar cm =
rect 1 1
# fillTexture grad
# lw none
where
stops = map (\(x,c) -> (c,fromRational x)) (colourList cm)
grad = mkLinearGradient stops origin unitX
pathColourBar :: Int -> ColourMap -> Diagram V2
pathColourBar n cm = ifoldMap mkR xs
where
mkR i x = rect d' 1
# alignR
# fc (cm ^. ixColourR (x - 1/(2*fromIntegral n)))
# translateX (fromRational x)
# lw none
where
d' | i == 0 = d
| otherwise = d*1.5
xs = tail (enumFromToN 0 1 n)
d = 1 / fromIntegral n
flipX_Y :: Num n => V2 n -> V2 n
flipX_Y (V2 x y) = V2 (-y) (-x)
_reflectionX_Y :: (Additive v, R2 v, Num n) => Transformation v n
_reflectionX_Y = undefined
_reflectX_Y :: (InSpace v n t, R2 v, Transformable t) => t -> t
_reflectX_Y = transform _reflectionX_Y