{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module Plots.Legend
(
Legend
, HasLegend (..)
, drawLegend
) where
import Control.Lens hiding (none, ( # ))
import Data.Default
import Data.Typeable
import Diagrams.TwoD.Text
import Geometry.BoundingBox
import Diagrams.Prelude hiding (orient)
import Plots.Types
data Legend = Legend
{ lPlacement :: Placement
, lGap :: Double
, lStyle :: Style V2 Double
, lSpacing :: Double
, lTextWidth :: Double
, lTextF :: String -> Diagram V2
, lTextStyle :: Style V2 Double
, lOrientation :: Orientation
, lVisible :: Bool
} deriving Typeable
type instance V Legend = V2
type instance N Legend = Double
class HasLegend a where
legend :: Lens' a Legend
legendPlacement :: Lens' a Placement
legendPlacement = legend . lens lPlacement (\l a -> l {lPlacement = a})
legendGap :: Lens' a Double
legendGap = legend . lens lGap (\l a -> l {lGap = a})
legendStyle :: Lens' a (Style V2 Double)
legendStyle = legend . lens lStyle (\l a -> l {lStyle = a})
legendSpacing :: Lens' a Double
legendSpacing = legend . lens lSpacing (\l a -> l {lSpacing = a})
legendTextWidth :: Lens' a Double
legendTextWidth = legend . lens lTextWidth (\l a -> l {lTextWidth = a})
legendTextFunction :: Lens' a (String -> Diagram V2)
legendTextFunction = legend . lens lTextF (\l a -> l {lTextF = a})
legendTextStyle :: Lens' a (Style V2 Double)
legendTextStyle = legend . lens lTextStyle (\l a -> l {lTextStyle = a})
legendOrientation :: Lens' a Orientation
legendOrientation = legend . lens lOrientation (\l a -> l {lOrientation = a})
instance HasLegend Legend where
legend = id
instance HasGap Legend where
gap = legendGap
instance HasPlacement Legend where
placement = legendPlacement
instance Default Legend where
def = Legend
{ lPlacement = rightTop
, lGap = 20
, lSpacing = 20
, lTextWidth = 60
, lStyle = mempty
, lTextF = mkText (BoxAlignedText 0 0.5)
, lTextStyle = mempty & fontSize (output 11)
, lOrientation = Vertical
, lVisible = True
}
instance HasVisibility Legend where
visible = lens lVisible (\l a -> l {lVisible = a})
instance ApplyStyle Legend
instance HasStyle Legend where
style = legendStyle
{-# INLINE style #-}
instance HasOrientation Legend where
orientation = legendOrientation
drawLegend
:: BoundingBox V2 Double
-> [(Diagram V2, String)]
-> Legend
-> Diagram V2
drawLegend bb entries l
| l ^. hidden || null entries = mempty
| otherwise = placeAgainst
bb
(l ^. legendPlacement)
(l ^. legendGap)
(ledge <> back)
where
w = l ^. legendTextWidth
h = l ^. legendSpacing
ledge = map mkLabels entries
# orient (l ^. legendOrientation) hcat vcat
# alignTL
back = backRect
# applyStyle (l ^. legendStyle)
# alignTL
backRect = orient (l ^. legendOrientation)
(rect (nEntries * entryWidth) h )
(rect entryWidth (h * nEntries))
nEntries = fromIntegral (length entries)
entryWidth = w + 10 + h
mkLabels (pic, txt) = strutX 5 ||| pic' ||| strutX 5 ||| label where
pic' = pic # withEnvelope (fromCorners (pure (-h/2)) (pure (h/2)))
label = view legendTextFunction l txt
# applyStyle (l ^. legendTextStyle)
# withEnvelope (fromCorners origin (mkP2 w h) # moveTo (mkP2 0 (-h/2)))