{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Plots.Types
(
PlotOptions
, HasPlotOptions (..)
, key
, addLegendEntry
, PlotMods
, plotMods
, Plotable (..)
, Plot
, mkPlot
, rawPlot
, DynamicPlot (..)
, _DynamicPlot
, dynamicPlot
, dynamicPlotMods
, StyledPlot
, styledPlot
, styleDynamic
, renderStyledPlot
, singleStyledPlotLegend
, styledPlotLegends
, HasVisibility (..)
, hide
, display
, Orientation (..)
, HasOrientation (..)
, orient
, horizontal
, vertical
, LegendEntry
, LegendPic (..)
, mkLegendEntry
, legendPicture
, legendText
, legendPrecedence
, AxisSpec (..)
, specTrans
, specBounds
, specScale
, scaleNum
, specPoint
, specColourMap
, Placement (..)
, HasPlacement (..)
, HasGap (..)
, placeAgainst
, topLeft, top, topRight, left, right, bottomLeft, bottom
, bottomRight
, leftAbove, leftTop, leftMid, leftBottom, leftBelow, midAbove, midBelow
, rightAbove, rightTop, rightMid, rightBottom, rightBelow
) where
import Control.Monad.State
import Data.Bool
import Data.List (sortBy)
import Data.Maybe (fromMaybe)
import Data.Ord (comparing)
import Data.Orphans ()
import Data.Typeable
import Diagrams.Prelude as D hiding (orient)
import Plots.Axis.Scale
import Plots.Style
import Plots.Util
import Diagrams.Combinators as D
import Geometry.TwoD.Shapes
import Diagrams.Types
data Orientation = Horizontal | Vertical
deriving (Show, Eq, Ord, Typeable)
orient :: HasOrientation o => o -> a -> a -> a
orient o h v =
case view orientation o of
Horizontal -> h
Vertical -> v
class HasOrientation a where
orientation :: Lens' a Orientation
instance HasOrientation Orientation where
orientation = id
horizontal :: HasOrientation a => Lens' a Bool
horizontal = orientation . iso (==Horizontal) (bool Vertical Horizontal)
vertical :: HasOrientation a => Lens' a Bool
vertical = horizontal . involuted not
class HasGap a where
gap :: Lens' a Double
data Placement = Placement
{ pAt :: V2 Rational
, pAnchor :: V2 Rational
, pGapDir :: Direction V2 Double
}
deriving (Show, Eq)
class HasPlacement a where
placement :: Lens' a Placement
placementAt :: Lens' a (V2 Rational)
placementAt = placement . lens pAt (\p a -> p {pAt = a})
placementAnchor :: Lens' a (V2 Rational)
placementAnchor = placement . lens pAnchor (\p a -> p {pAnchor = a})
gapDirection :: Lens' a (Direction V2 Double)
gapDirection = placement . lens pGapDir (\p a -> p {pGapDir = a})
instance HasPlacement Placement where
placement = id
pInside :: V2 Rational -> Placement
pInside v = Placement
{ pAt = v
, pAnchor = v
, pGapDir = dirBetween' (P $ fromRational <$> v) origin
}
dirBetween' :: (Metric v, Floating n) => Point v n -> Point v n -> Direction v n
dirBetween' p q = direction $ q .-. p
topLeft, top, topRight, left, right, bottomLeft, bottom, bottomRight :: Placement
topLeft = pInside (V2 (-1) 1 )
top = pInside (V2 0 1 )
topRight = pInside (V2 1 1 )
left = pInside (V2 (-1) 0 )
right = pInside (V2 (-1) 0 )
bottomLeft = pInside (V2 (-1) (-1))
bottom = pInside (V2 0 (-1))
bottomRight = pInside (V2 1 (-1))
leftAbove, leftTop, leftMid, leftBottom, leftBelow, midAbove, midBelow,
rightAbove, rightTop, rightMid, rightBottom, rightBelow :: Placement
leftAbove = Placement (V2 (-1) 1 ) (V2 (-1) (-1)) (direction (V2 0 1 ))
leftTop = Placement (V2 (-1) 1 ) (V2 1 1 ) (direction (V2 (-1) 0 ))
leftMid = Placement (V2 (-1) 0 ) (V2 1 0 ) (direction (V2 (-1) 0 ))
leftBottom = Placement (V2 (-1) (-1)) (V2 1 (-1)) (direction (V2 (-1) 0 ))
leftBelow = Placement (V2 (-1) (-1)) (V2 (-1) 1 ) (direction (V2 0 (-1)))
midAbove = Placement (V2 0 1 ) (V2 0 (-1)) (direction (V2 0 1 ))
midBelow = Placement (V2 0 (-1)) (V2 0 1 ) (direction (V2 0 (-1)))
rightAbove = Placement (V2 1 1 ) (V2 1 (-1)) (direction (V2 0 1 ))
rightTop = Placement (V2 1 1 ) (V2 (-1) 1 ) (direction (V2 1 0 ))
rightMid = Placement (V2 1 0 ) (V2 (-1) 0 ) (direction (V2 1 0 ))
rightBottom = Placement (V2 1 (-1)) (V2 (-1) (-1)) (direction (V2 1 0 ))
rightBelow = Placement (V2 1 (-1)) (V2 1 1 ) (direction (V2 0 (-1)))
placeAgainst
:: (InSpace V2 n a, SameSpace a b, Enveloped a, Enveloped b, HasOrigin b)
=> a -> Placement -> n -> b -> b
placeAgainst a (Placement (V2 px py) (V2 ax ay) d) n b
= b # anchor
# moveTo (pos .+^ n *^ fromDirection (realToFrac <$> d))
where
pos = mkP2 (lerp' px xu xl) (lerp' py yu yl)
anchor = alignBy unitX (fromRational ax) . alignBy unitY (fromRational ay)
(P (V2 xl yl), P (V2 xu yu)) = fromMaybe (origin, origin) (getCorners $ boundingBox a)
lerp' z u v = fromRational alpha * u + (1 - fromRational alpha) * v
where alpha = (z + 1) / 2
data LegendPic v
= DefaultLegendPic
| CustomLegendPic (PlotStyle v -> Diagram v)
instance Default (LegendPic v) where
def = DefaultLegendPic
data LegendEntry v = LegendEntry
{ lPic :: LegendPic v
, lText :: String
, lPrecedence :: Double
} deriving Typeable
legendPicture :: Lens' (LegendEntry v) (LegendPic v)
legendPicture = lens lPic (\l pic -> l {lPic = pic})
legendText :: Lens' (LegendEntry v) String
legendText = lens lText (\l txt -> l {lText = txt})
legendPrecedence :: Lens' (LegendEntry v) Double
legendPrecedence = lens lPrecedence (\l n -> l {lPrecedence = n})
type instance V (LegendEntry v) = v
type instance N (LegendEntry v) = Double
mkLegendEntry :: String -> LegendEntry v
mkLegendEntry x = LegendEntry DefaultLegendPic x 0
data PlotOptions v = PlotOptions
{ poName :: Name
, poClipPlot :: Bool
, poLegend :: [LegendEntry v]
, poVisible :: Bool
, poTransform :: Transformation v Double
} deriving Typeable
type instance V (PlotOptions v) = v
type instance N (PlotOptions v) = Double
class HasPlotOptions f a where
{-# MINIMAL plotOptions #-}
plotOptions :: LensLike' f a (PlotOptions (V a))
plotName :: Functor f => LensLike' f a Name
plotName = plotOptions . lens poName (\g a -> g {poName = a})
{-# INLINE plotName #-}
clipPlot :: Functor f => LensLike' f a Bool
clipPlot = plotOptions . lens poClipPlot (\g a -> g {poClipPlot = a})
{-# INLINE clipPlot #-}
legendEntries :: Functor f => LensLike' f a [LegendEntry (V a)]
legendEntries = plotOptions . lens poLegend (\g a -> g {poLegend = a})
{-# INLINE legendEntries #-}
plotTransform :: Functor f => LensLike' f a (Transformation (V a) Double)
plotTransform = plotOptions . lens poTransform (\g a -> g {poTransform = a})
{-# INLINE plotTransform #-}
plotVisible :: Functor f => LensLike' f a Bool
plotVisible = plotOptions . lens poVisible (\po b -> po {poVisible = b})
{-# INLINE plotVisible #-}
instance (HasBasis v, Foldable v) => Default (PlotOptions v) where
def = PlotOptions
{ poName = mempty
, poClipPlot = True
, poLegend = []
, poVisible = True
, poTransform = mempty
}
instance HasPlotOptions f (PlotOptions v) where
plotOptions = id
{-# INLINE plotOptions #-}
instance HasLinearMap v => Transformable (PlotOptions v) where
transform = over plotTransform . transform
instance Additive v => HasOrigin (PlotOptions v) where
moveOriginTo = over plotTransform . moveOriginTo
instance Qualifiable (PlotOptions v) where
n .>> p = over plotName (n .>>) p
key :: (HasPlotOptions Identity a, MonadState a m) => String -> m ()
key = addLegendEntry . mkLegendEntry
addLegendEntry
:: (HasPlotOptions Identity a, MonadState a m)
=> LegendEntry (V a)
-> m ()
addLegendEntry l = legendEntries <>= [l]
data AxisSpec v = AxisSpec
{ _specBounds :: v (Double, Double)
, _specTrans :: Transformation v Double
, _specScale :: v LogScale
, _specColourMap :: ColourMap
}
makeLenses ''AxisSpec
type instance V (AxisSpec v) = v
type instance N (AxisSpec v) = Double
scaleNum :: Floating n => (n, n) -> LogScale -> n -> n
scaleNum (a,b) s x = case s of
LinearAxis -> x
LogAxis -> subtract a $ (b / logBase 10 d) * (logBase 10 x)
where d = b - a
specPoint
:: (Applicative v, Additive v, Foldable v)
=> AxisSpec v -> Point v Double -> Point v Double
specPoint (AxisSpec bs tr ss _) p =
papply tr $ over _Point (scaleNum <$> bs <*> ss <*>) p
class (Typeable p, Enveloped p, N p ~ Double) => Plotable p where
renderPlotable
:: InSpace v Double p
=> AxisSpec v
-> PlotStyle v
-> p
-> Diagram v
defLegendPic
:: InSpace v Double p
=> PlotStyle v
-> p
-> Diagram v
defLegendPic = mempty
instance (Typeable v, HasLinearMap v) => Plotable (Diagram v) where
renderPlotable s _ dia = dia # transform (s^.specTrans)
strokePathV :: (Typeable v, Metric v, Typeable n, OrderedField n) => Path v n -> QDiagram v n Any
strokePathV path = mkQD (Prim path) (getEnvelope path) mempty mempty
instance (Typeable v, R1 v, HasLinearMap v) => Plotable (Path v Double) where
renderPlotable s sty path
= strokePathV path
# transform (s^.specTrans)
# applyLineStyle sty
defLegendPic sty _
= strokePathV (fromVertices [(-10) *^ unitX, 10 *^ unitX])
# applyLineStyle sty
class HasVisibility a where
visible :: Lens' a Bool
hidden :: Lens' a Bool
hidden = visible . involuted not
{-# INLINE hidden #-}
instance HasVisibility (PlotOptions v) where
visible = plotVisible
instance HasVisibility (PlotMods v) where
visible = plotVisible
instance HasVisibility (Plot p) where
visible = plotVisible
instance HasVisibility (DynamicPlot v) where
visible = plotVisible
instance HasVisibility (StyledPlot v) where
visible = plotVisible
hide :: (MonadState s m, HasVisibility a) => ASetter' s a -> m ()
hide l = l . visible .= False
display :: (MonadState s m, HasVisibility a) => ASetter' s a -> m ()
display l = l . visible .= True
data PlotMods v
= PlotMods (PlotOptions v) (PlotStyle v -> PlotStyle v)
type instance V (PlotMods v) = v
type instance N (PlotMods v) = Double
instance Functor f => HasPlotOptions f (PlotMods v) where
plotOptions f (PlotMods opts sty) = f opts <&> \opts' -> PlotMods opts' sty
instance Settable f => HasPlotStyle f (PlotMods v) where
plotStyle = sty . mapped where
sty f (PlotMods opts s) = f s <&> \s' -> PlotMods opts s'
instance (HasBasis v, Foldable v) => Default (PlotMods v) where
def = PlotMods def id
data Plot p =
Plot p
(PlotOptions (V p))
(PlotStyle (V p) -> PlotStyle (V p))
deriving Typeable
type instance V (Plot p) = V p
type instance N (Plot p) = Double
instance Functor f => HasPlotOptions f (Plot p) where
plotOptions f (Plot p opts sty) = f opts <&> \opts' -> Plot p opts' sty
instance Settable f => HasPlotStyle f (Plot p) where
plotStyle = sty . mapped where
sty f (Plot p opts s) = f s <&> \s' -> Plot p opts s'
instance HasOrientation p => HasOrientation (Plot p) where
orientation = rawPlot . orientation
mkPlot :: (InSpace v Double p, HasBasis v, Foldable v) => p -> Plot p
mkPlot p = Plot p def id
rawPlot :: SameSpace p p' => Lens (Plot p) (Plot p') p p'
rawPlot f (Plot p opts ps) = f p <&> \p' -> Plot p' opts ps
plotMods :: Lens' (Plot p) (PlotMods (V p))
plotMods f (Plot p opts ps) =
f (PlotMods opts ps) <&> \(PlotMods opts' ps') -> Plot p opts' ps'
data DynamicPlot v where
DynamicPlot :: (InSpace v Double p, Plotable p) => Plot p -> DynamicPlot v
deriving Typeable
type instance V (DynamicPlot v) = v
type instance N (DynamicPlot v) = Double
_DynamicPlot :: Plotable p => Prism' (DynamicPlot (V p)) (Plot p)
_DynamicPlot = prism' DynamicPlot (\(DynamicPlot p) -> cast p)
dynamicPlot :: forall p. Typeable p => Traversal' (DynamicPlot (V p)) (Plot p)
dynamicPlot f d@(DynamicPlot p) =
case eq p of
Just Refl -> f p <&> \p' -> DynamicPlot p'
Nothing -> pure d
where eq :: Typeable a => a -> Maybe (a :~: Plot p)
eq _ = eqT
instance Functor f => HasPlotOptions f (DynamicPlot v) where
plotOptions f (DynamicPlot (Plot p opts sty)) =
f opts <&> \opts' -> DynamicPlot (Plot p opts' sty)
instance Settable f => HasPlotStyle f (DynamicPlot v) where
plotStyle = sty . mapped where
sty :: Setter' (DynamicPlot v) (PlotStyle v -> PlotStyle v)
sty f (DynamicPlot (Plot p opts s)) = f s <&> \s' -> DynamicPlot (Plot p opts s')
dynamicPlotMods :: Lens' (DynamicPlot v) (PlotMods v)
dynamicPlotMods f (DynamicPlot (Plot p opts ps)) =
f (PlotMods opts ps) <&> \(PlotMods opts' ps') -> DynamicPlot (Plot p opts' ps')
data StyledPlot v where
StyledPlot
:: Plotable p
=> p
-> PlotOptions (V p)
-> PlotStyle (V p)
-> StyledPlot (V p)
type instance V (StyledPlot v) = v
type instance N (StyledPlot v) = Double
instance Functor f => HasPlotOptions f (StyledPlot v) where
plotOptions f (StyledPlot p opts sty) =
f opts <&> \opts' -> StyledPlot p opts' sty
instance HasLinearMap v => Enveloped (StyledPlot v) where
getEnvelope (StyledPlot p opts _) =
getEnvelope p & transform (poTransform opts)
instance Functor f => HasPlotStyle f (StyledPlot v) where
plotStyle f (StyledPlot p opts sty) =
f sty <&> StyledPlot p opts
styledPlot :: forall p. Typeable p => Traversal' (StyledPlot (V p)) p
styledPlot f s@(StyledPlot p opts sty) =
case eq p of
Just Refl -> f p <&> \p' -> StyledPlot p' opts sty
Nothing -> pure s
where eq :: Typeable a => a -> Maybe (a :~: p)
eq _ = eqT
styleDynamic :: PlotStyle v -> DynamicPlot v -> StyledPlot v
styleDynamic sty (DynamicPlot (Plot p opts styF)) = StyledPlot p opts (styF sty)
renderStyledPlot :: HasLinearMap v => AxisSpec v -> StyledPlot v -> Diagram v
renderStyledPlot aSpec (StyledPlot p opts sty)
= renderPlotable aSpec sty p
& whenever (opts^.hidden) D.phantom
specRect :: AxisSpec V2 -> Path V2 Double
specRect aSpec =
rect (xU - xL) (yU - yL)
# moveTo (mkP2 ((xU+xL)/2) ((yU+yL)/2))
# transform t
where
V2 (xL,xU) (yL,yU) = _specBounds aSpec
t = _specTrans aSpec
singleStyledPlotLegend :: StyledPlot v -> [(Double, Diagram v, String)]
singleStyledPlotLegend (StyledPlot p opts sty) =
map mk (opts ^. legendEntries)
where
mk entry = (entry ^. legendPrecedence, pic, entry ^. legendText)
where
pic = case lPic entry of
DefaultLegendPic -> defLegendPic sty p
CustomLegendPic f -> f sty
styledPlotLegends :: [StyledPlot v] -> [(Diagram v, String)]
styledPlotLegends
= map (\(_,p,t) -> (p,t))
. sortOn (view _1)
. concatMap singleStyledPlotLegend
sortOn :: Ord b => (a -> b) -> [a] -> [a]
sortOn f =
map snd . sortBy (comparing fst) . map (\x -> let y = f x in y `seq` (y, x))