{-# 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 b v n = TextAlignment n -> String -> QDiagram b v n Any
data AxisLabelPosition
= MiddleAxisLabel
| LowerAxisLabel
| UpperAxisLabel
data AxisLabelPlacement
= InsideAxisLabel
| OutsideAxisLabel
data AxisLabel b v n = AxisLabel
{ alFun :: TextFunction b v n
, alText :: String
, alStyle :: Style v n
, alGap :: n
, alPos :: AxisLabelPosition
, alPlacement :: AxisLabelPlacement
, alVisible :: Bool
}
type instance V (AxisLabel b v n) = v
type instance N (AxisLabel b v n) = n
class HasAxisLabel f a b | a -> b where
axisLabel :: LensLike' f a (AxisLabel b (V a) (N a))
axisLabelText :: Functor f => LensLike' f a String
axisLabelText = axisLabel . lens alText (\al txt -> al {alText = txt})
axisLabelTextFunction :: Functor f => LensLike' f a (TextFunction b (V a) (N a))
axisLabelTextFunction = axisLabel . lens alFun (\al f -> al {alFun = f})
axisLabelGap :: Functor f => LensLike' f a (N a)
axisLabelGap = axisLabel . lens alGap (\al sty -> al {alGap = sty})
axisLabelStyle :: Functor f => LensLike' f a (Style (V a) (N a))
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 b v n) b where
axisLabel = id
instance Typeable n => HasStyle (AxisLabel b v n) where
applyStyle = over axisLabelStyle . applyStyle
instance HasVisibility (AxisLabel b v n) where
visible = lens alVisible (\al b -> al {alVisible = b})
instance HasGap (AxisLabel b v n) where
gap = axisLabelGap
instance (TypeableFloat n, Renderable (Text n) b)
=> Default (AxisLabel b V2 n) where
def = AxisLabel
{ alFun = mkText
, alText = ""
, alStyle = mempty & fontSize (output 11)
& recommendFillColor black
, alGap = 30
, alPos = MiddleAxisLabel
, alPlacement = OutsideAxisLabel
, alVisible = True
}
data TickLabels b v n = TickLabels
{ tlFun :: [n] -> (n,n) -> [(n, String)]
, tlTextFun :: TextFunction b v n
, tlStyle :: Style v n
, tlGap :: n
, tlVisible :: Bool
} deriving Typeable
type instance V (TickLabels b v n) = v
type instance N (TickLabels b v n) = n
class HasTickLabels f a b | a -> b where
tickLabel :: LensLike' f a (TickLabels b (V a) (N a))
tickLabelTextFunction :: Functor f => LensLike' f a (TextFunction b (V a) (N a))
tickLabelTextFunction = tickLabel . lens tlTextFun (\tl f -> tl {tlTextFun = f})
tickLabelFunction :: Functor f => LensLike' f a ([N a] -> (N a, N a) -> [(N a, String)])
tickLabelFunction = tickLabel . lens tlFun (\tl f -> tl {tlFun = f})
tickLabelStyle :: Functor f => LensLike' f a (Style (V a) (N a))
tickLabelStyle = tickLabel . lens tlStyle (\tl sty -> tl {tlStyle = sty})
tickLabelGap :: Functor f => LensLike' f a (N a)
tickLabelGap = tickLabel . lens tlGap (\tl n -> tl {tlGap = n})
instance HasTickLabels f (TickLabels b v n) b where
tickLabel = id
instance HasGap (TickLabels b v n) where
gap = tickLabelGap
instance (TypeableFloat n, Renderable (Text n) b)
=> Default (TickLabels b V2 n) where
def = TickLabels
{ tlFun = atMajorTicks floatShow
, tlTextFun = mkText
, tlStyle = mempty & fontSize (output 11)
& recommendFillColor black
, tlGap = 12
, tlVisible = True
}
instance HasVisibility (TickLabels b v n) where
visible = lens tlVisible (\tl b -> tl {tlVisible = b})
tickLabelPositions
:: (HasTickLabels f a b, Settable f)
=> LensLike' f a [(N a, String)]
tickLabelPositions = tickLabelFunction . mapped . mapped
floatShow :: Real n => n -> String
floatShow = show . (realToFrac :: Real n => n -> Float)
atMajorTicks :: (n -> String) -> [n] -> (n,n) -> [(n, String)]
atMajorTicks f ticks _ = map ((,) <*> f) ticks