module Graphics.Rendering.Chart.Axis.Indexed(
PlotIndex(..),
autoIndexAxis,
addIndexes,
) where
import Control.Arrow (first)
import Data.Default.Class
import Graphics.Rendering.Chart.Axis.Types
newtype PlotIndex = PlotIndex { plotindex_i :: Int }
deriving (Eq,Ord,Enum,Num,Real,Integral,Show)
instance PlotValue PlotIndex where
toValue (PlotIndex i) = fromIntegral i
fromValue = PlotIndex . round
autoAxis = autoIndexAxis []
addIndexes :: [a] -> [(PlotIndex,a)]
addIndexes as = map (first PlotIndex) (zip [0..] as)
autoIndexAxis :: Integral i => [String] -> [i] -> AxisData i
autoIndexAxis labels vs = AxisData {
_axis_visibility = def { _axis_show_ticks = False },
_axis_viewport = vport,
_axis_tropweiv = invport,
_axis_ticks = [],
_axis_labels = [filter (\(i,_) -> i >= imin && i <= imax)
(zip [0..] labels)],
_axis_grid = []
}
where
vport r i = linMap id ( fromIntegral imin 0.5
, fromIntegral imax + 0.5) r (fromIntegral i)
invport = invLinMap round fromIntegral (imin, imax)
imin = minimum vs
imax = maximum vs