{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
module Plots.Axis.Labels
(
HasAxisLabel (..)
, AxisLabel
, AxisLabelPosition (..)
, AxisLabelPlacement (..)
, TickLabels
, HasTickLabels (..)
, tickLabelPositions
, atMajorTicks
, TextFunction
) where
import Control.Lens hiding (( # ))
import Data.Data
import Data.Default
import Diagrams.Prelude hiding (view)
import Diagrams.TwoD.Text
import Plots.Types
type TextFunction v = TextAlignment Double -> String -> Diagram v
data AxisLabelPosition
= MiddleAxisLabel
| LowerAxisLabel
| UpperAxisLabel
data AxisLabelPlacement
= InsideAxisLabel
| OutsideAxisLabel
data AxisLabel v = AxisLabel
{ alFun :: TextFunction v
, alText :: String
, alStyle :: Style v Double
, alGap :: Double
, alPos :: AxisLabelPosition
, alPlacement :: AxisLabelPlacement
, alVisible :: Bool
}
type instance V (AxisLabel v) = v
type instance N (AxisLabel v) = Double
class HasAxisLabel f a where
axisLabel :: LensLike' f a (AxisLabel (V a))
axisLabelText :: Functor f => LensLike' f a String
axisLabelText = axisLabel . lens alText (\al txt -> al {alText = txt})
axisLabelTextFunction :: Functor f => LensLike' f a (TextFunction (V a))
axisLabelTextFunction = axisLabel . lens alFun (\al f -> al {alFun = f})
axisLabelGap :: Functor f => LensLike' f a Double
axisLabelGap = axisLabel . lens alGap (\al sty -> al {alGap = sty})
axisLabelStyle :: Functor f => LensLike' f a (Style (V a) Double)
axisLabelStyle = axisLabel . lens alStyle (\al sty -> al {alStyle = sty})
axisLabelPosition :: Functor f => LensLike' f a AxisLabelPosition
axisLabelPosition = axisLabel . lens alPos (\al sty -> al {alPos = sty})
axisLabelPlacement :: Functor f => LensLike' f a AxisLabelPosition
axisLabelPlacement = axisLabel . lens alPos (\al sty -> al {alPos = sty})
instance HasAxisLabel f (AxisLabel v) where
axisLabel = id
instance ApplyStyle (AxisLabel v)
instance HasStyle (AxisLabel v) where
style = axisLabelStyle
instance HasVisibility (AxisLabel v) where
visible = lens alVisible (\al b -> al {alVisible = b})
instance HasGap (AxisLabel v) where
gap = axisLabelGap
instance Default (AxisLabel V2) where
def = AxisLabel
{ alFun = mkText
, alText = ""
, alStyle = mempty & fontSize (output 11)
& backupFillColor black
, alGap = 30
, alPos = MiddleAxisLabel
, alPlacement = OutsideAxisLabel
, alVisible = True
}
instance Default (AxisLabel V3) where
def = AxisLabel
{ alFun = mempty
, alText = ""
, alStyle = mempty & fontSize (output 11)
, alGap = 30
, alPos = MiddleAxisLabel
, alPlacement = OutsideAxisLabel
, alVisible = True
}
data TickLabels v = TickLabels
{ tlFun :: [Double] -> (Double,Double) -> [(Double, String)]
, tlTextFun :: TextFunction v
, tlStyle :: Style v Double
, tlGap :: Double
, tlVisible :: Bool
} deriving Typeable
type instance V (TickLabels v) = v
type instance N (TickLabels v) = Double
class HasTickLabels f a where
tickLabel :: LensLike' f a (TickLabels (V a))
tickLabelTextFunction :: Functor f => LensLike' f a (TextFunction (V a))
tickLabelTextFunction = tickLabel . lens tlTextFun (\tl f -> tl {tlTextFun = f})
tickLabelFunction :: Functor f => LensLike' f a ([Double] -> (Double, Double) -> [(Double, String)])
tickLabelFunction = tickLabel . lens tlFun (\tl f -> tl {tlFun = f})
tickLabelStyle :: Functor f => LensLike' f a (Style (V a) Double)
tickLabelStyle = tickLabel . lens tlStyle (\tl sty -> tl {tlStyle = sty})
tickLabelGap :: Functor f => LensLike' f a Double
tickLabelGap = tickLabel . lens tlGap (\tl n -> tl {tlGap = n})
instance HasTickLabels f (TickLabels v) where
tickLabel = id
instance HasGap (TickLabels v) where
gap = tickLabelGap
instance Default (TickLabels V2) where
def = TickLabels
{ tlFun = atMajorTicks floatShow
, tlTextFun = mkText
, tlStyle = mempty & fontSize (output 11)
& backupFillColor black
, tlGap = 12
, tlVisible = True
}
instance Default (TickLabels V3) where
def = TickLabels
{ tlFun = atMajorTicks floatShow
, tlTextFun = mempty
, tlStyle = mempty & fontSize (output 11)
, tlGap = 12
, tlVisible = True
}
instance HasVisibility (TickLabels v) where
visible = lens tlVisible (\tl b -> tl {tlVisible = b})
tickLabelPositions
:: (HasTickLabels f a, Settable f) => LensLike' f a [(Double, String)]
tickLabelPositions = tickLabelFunction . mapped . mapped
floatShow :: Real n => n -> String
floatShow = show . (realToFrac :: Real n => n -> Float)
atMajorTicks :: (Double -> String) -> [Double] -> (Double,Double) -> [(Double, String)]
atMajorTicks f ticks _ = map ((,) <*> f) ticks