{-# OPTIONS_GHC -fno-warn-orphans #-}
module Graphics.Rendering.Chart.Axis.Int(
defaultIntAxis,
scaledIntAxis,
autoScaledIntAxis
) where
import Data.List(genericLength)
import Data.Int (Int8, Int16, Int32, Int64)
import Data.Word (Word8, Word16, Word32, Word64)
import Graphics.Rendering.Chart.Geometry
import Graphics.Rendering.Chart.Axis.Types
import Graphics.Rendering.Chart.Axis.Floating
instance PlotValue Int where
toValue :: Int -> Double
toValue = Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral
fromValue :: Double -> Int
fromValue = Double -> Int
forall a b. (RealFrac a, Integral b) => a -> b
round
autoAxis :: AxisFn Int
autoAxis = LinearAxisParams Int -> AxisFn Int
forall i.
(Integral i, PlotValue i) =>
LinearAxisParams i -> AxisFn i
autoScaledIntAxis LinearAxisParams Int
forall a. Show a => LinearAxisParams a
defaultIntAxis
instance PlotValue Int8 where
toValue :: Int8 -> Double
toValue = Int8 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral
fromValue :: Double -> Int8
fromValue = Double -> Int8
forall a b. (RealFrac a, Integral b) => a -> b
round
autoAxis :: AxisFn Int8
autoAxis = LinearAxisParams Int8 -> AxisFn Int8
forall i.
(Integral i, PlotValue i) =>
LinearAxisParams i -> AxisFn i
autoScaledIntAxis LinearAxisParams Int8
forall a. Show a => LinearAxisParams a
defaultIntAxis
instance PlotValue Int16 where
toValue :: Int16 -> Double
toValue = Int16 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral
fromValue :: Double -> Int16
fromValue = Double -> Int16
forall a b. (RealFrac a, Integral b) => a -> b
round
autoAxis :: AxisFn Int16
autoAxis = LinearAxisParams Int16 -> AxisFn Int16
forall i.
(Integral i, PlotValue i) =>
LinearAxisParams i -> AxisFn i
autoScaledIntAxis LinearAxisParams Int16
forall a. Show a => LinearAxisParams a
defaultIntAxis
instance PlotValue Int32 where
toValue :: Int32 -> Double
toValue = Int32 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral
fromValue :: Double -> Int32
fromValue = Double -> Int32
forall a b. (RealFrac a, Integral b) => a -> b
round
autoAxis :: AxisFn Int32
autoAxis = LinearAxisParams Int32 -> AxisFn Int32
forall i.
(Integral i, PlotValue i) =>
LinearAxisParams i -> AxisFn i
autoScaledIntAxis LinearAxisParams Int32
forall a. Show a => LinearAxisParams a
defaultIntAxis
instance PlotValue Int64 where
toValue :: Int64 -> Double
toValue = Int64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral
fromValue :: Double -> Int64
fromValue = Double -> Int64
forall a b. (RealFrac a, Integral b) => a -> b
round
autoAxis :: AxisFn Int64
autoAxis = LinearAxisParams Int64 -> AxisFn Int64
forall i.
(Integral i, PlotValue i) =>
LinearAxisParams i -> AxisFn i
autoScaledIntAxis LinearAxisParams Int64
forall a. Show a => LinearAxisParams a
defaultIntAxis
instance PlotValue Word where
toValue :: Word -> Double
toValue = Word -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral
fromValue :: Double -> Word
fromValue = Double -> Word
forall a b. (RealFrac a, Integral b) => a -> b
round
autoAxis :: AxisFn Word
autoAxis = LinearAxisParams Word -> AxisFn Word
forall i.
(Integral i, PlotValue i) =>
LinearAxisParams i -> AxisFn i
autoScaledIntAxis LinearAxisParams Word
forall a. Show a => LinearAxisParams a
defaultIntAxis
instance PlotValue Word8 where
toValue :: Word8 -> Double
toValue = Word8 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral
fromValue :: Double -> Word8
fromValue = Double -> Word8
forall a b. (RealFrac a, Integral b) => a -> b
round
autoAxis :: AxisFn Word8
autoAxis = LinearAxisParams Word8 -> AxisFn Word8
forall i.
(Integral i, PlotValue i) =>
LinearAxisParams i -> AxisFn i
autoScaledIntAxis LinearAxisParams Word8
forall a. Show a => LinearAxisParams a
defaultIntAxis
instance PlotValue Word16 where
toValue :: Word16 -> Double
toValue = Word16 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral
fromValue :: Double -> Word16
fromValue = Double -> Word16
forall a b. (RealFrac a, Integral b) => a -> b
round
autoAxis :: AxisFn Word16
autoAxis = LinearAxisParams Word16 -> AxisFn Word16
forall i.
(Integral i, PlotValue i) =>
LinearAxisParams i -> AxisFn i
autoScaledIntAxis LinearAxisParams Word16
forall a. Show a => LinearAxisParams a
defaultIntAxis
instance PlotValue Word32 where
toValue :: Word32 -> Double
toValue = Word32 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral
fromValue :: Double -> Word32
fromValue = Double -> Word32
forall a b. (RealFrac a, Integral b) => a -> b
round
autoAxis :: AxisFn Word32
autoAxis = LinearAxisParams Word32 -> AxisFn Word32
forall i.
(Integral i, PlotValue i) =>
LinearAxisParams i -> AxisFn i
autoScaledIntAxis LinearAxisParams Word32
forall a. Show a => LinearAxisParams a
defaultIntAxis
instance PlotValue Word64 where
toValue :: Word64 -> Double
toValue = Word64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral
fromValue :: Double -> Word64
fromValue = Double -> Word64
forall a b. (RealFrac a, Integral b) => a -> b
round
autoAxis :: AxisFn Word64
autoAxis = LinearAxisParams Word64 -> AxisFn Word64
forall i.
(Integral i, PlotValue i) =>
LinearAxisParams i -> AxisFn i
autoScaledIntAxis LinearAxisParams Word64
forall a. Show a => LinearAxisParams a
defaultIntAxis
instance PlotValue Integer where
toValue :: Integer -> Double
toValue = Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral
fromValue :: Double -> Integer
fromValue = Double -> Integer
forall a b. (RealFrac a, Integral b) => a -> b
round
autoAxis :: AxisFn Integer
autoAxis = LinearAxisParams Integer -> AxisFn Integer
forall i.
(Integral i, PlotValue i) =>
LinearAxisParams i -> AxisFn i
autoScaledIntAxis LinearAxisParams Integer
forall a. Show a => LinearAxisParams a
defaultIntAxis
defaultIntAxis :: (Show a) => LinearAxisParams a
defaultIntAxis :: LinearAxisParams a
defaultIntAxis = LinearAxisParams :: forall a. ([a] -> [String]) -> Int -> Int -> LinearAxisParams a
LinearAxisParams {
_la_labelf :: [a] -> [String]
_la_labelf = (a -> String) -> [a] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map a -> String
forall a. Show a => a -> String
show,
_la_nLabels :: Int
_la_nLabels = Int
5,
_la_nTicks :: Int
_la_nTicks = Int
10
}
autoScaledIntAxis :: (Integral i, PlotValue i) =>
LinearAxisParams i -> AxisFn i
autoScaledIntAxis :: LinearAxisParams i -> AxisFn i
autoScaledIntAxis LinearAxisParams i
lap [i]
ps = LinearAxisParams i -> (i, i) -> AxisFn i
forall i.
(Integral i, PlotValue i) =>
LinearAxisParams i -> (i, i) -> AxisFn i
scaledIntAxis LinearAxisParams i
lap (i, i)
rs [i]
ps
where
rs :: (i, i)
rs = ([i] -> i
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
minimum [i]
ps,[i] -> i
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum [i]
ps)
scaledIntAxis :: (Integral i, PlotValue i) =>
LinearAxisParams i -> (i,i) -> AxisFn i
scaledIntAxis :: LinearAxisParams i -> (i, i) -> AxisFn i
scaledIntAxis LinearAxisParams i
lap (i
minI,i
maxI) [i]
ps =
([i] -> [String]) -> ([i], [i], [i]) -> AxisData i
forall x.
PlotValue x =>
([x] -> [String]) -> ([x], [x], [x]) -> AxisData x
makeAxis (LinearAxisParams i -> [i] -> [String]
forall a. LinearAxisParams a -> [a] -> [String]
_la_labelf LinearAxisParams i
lap) ([i]
labelvs,[i]
tickvs,[i]
gridvs)
where
range :: [a] -> (a, b)
range [] = (a
0,b
1)
range [a]
_ | i
minI i -> i -> Bool
forall a. Eq a => a -> a -> Bool
== i
maxI = (i -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (i -> a) -> i -> a
forall a b. (a -> b) -> a -> b
$ i
minIi -> i -> i
forall a. Num a => a -> a -> a
-i
1, i -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral (i -> b) -> i -> b
forall a b. (a -> b) -> a -> b
$ i
minIi -> i -> i
forall a. Num a => a -> a -> a
+i
1)
| Bool
otherwise = (i -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral i
minI, i -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral i
maxI)
labelvs :: [i]
labelvs = i -> Range -> [i]
forall a. Integral a => a -> Range -> [a]
stepsInt (Int -> i
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> i) -> Int -> i
forall a b. (a -> b) -> a -> b
$ LinearAxisParams i -> Int
forall a. LinearAxisParams a -> Int
_la_nLabels LinearAxisParams i
lap) Range
r
tickvs :: [i]
tickvs = i -> Range -> [i]
forall a. Integral a => a -> Range -> [a]
stepsInt (Int -> i
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> i) -> Int -> i
forall a b. (a -> b) -> a -> b
$ LinearAxisParams i -> Int
forall a. LinearAxisParams a -> Int
_la_nTicks LinearAxisParams i
lap)
( i -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (i -> Double) -> i -> Double
forall a b. (a -> b) -> a -> b
$ [i] -> i
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
minimum [i]
labelvs
, i -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (i -> Double) -> i -> Double
forall a b. (a -> b) -> a -> b
$ [i] -> i
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum [i]
labelvs )
gridvs :: [i]
gridvs = [i]
labelvs
r :: Range
r = [i] -> Range
forall a b a. (Num a, Num b) => [a] -> (a, b)
range [i]
ps
stepsInt :: Integral a => a -> Range -> [a]
stepsInt :: a -> Range -> [a]
stepsInt a
nSteps Range
range = a -> [a] -> [[a]] -> [a]
forall a. a -> [a] -> [[a]] -> [a]
bestSize ([a] -> a
forall a. [a] -> a
goodness [a]
alt0) [a]
alt0 [[a]]
alts
where
bestSize :: a -> [a] -> [[a]] -> [a]
bestSize a
n [a]
a ([a]
a':[[a]]
as) = let n' :: a
n' = [a] -> a
forall a. [a] -> a
goodness [a]
a' in
if a
n' a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
n then a -> [a] -> [[a]] -> [a]
bestSize a
n' [a]
a' [[a]]
as else [a]
a
bestSize a
_ [a]
_ [] = []
goodness :: [a] -> a
goodness [a]
vs = a -> a
forall a. Num a => a -> a
abs ([a] -> a
forall i a. Num i => [a] -> i
genericLength [a]
vs a -> a -> a
forall a. Num a => a -> a -> a
- a
nSteps)
([a]
alt0:[[a]]
alts) = (a -> [a]) -> [a] -> [[a]]
forall a b. (a -> b) -> [a] -> [b]
map (\a
n -> a -> Range -> [a]
forall a b a.
(RealFrac b, RealFrac a, Integral a) =>
a -> (a, b) -> [a]
steps a
n Range
range) [a]
sampleSteps'
sampleSteps' :: [a]
sampleSteps' = let rangeMag :: a
rangeMag = Double -> a
forall a b. (RealFrac a, Integral b) => a -> b
ceiling (Range -> Double
forall a b. (a, b) -> b
snd Range
range Double -> Double -> Double
forall a. Num a => a -> a -> a
- Range -> Double
forall a b. (a, b) -> a
fst Range
range)
([a]
s1,[a]
s2) = (a -> Bool) -> [a] -> ([a], [a])
forall a. (a -> Bool) -> [a] -> ([a], [a])
span (a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< (a
rangeMag a -> a -> a
forall a. Integral a => a -> a -> a
`div` a
nSteps)) [a]
sampleSteps
in (([a] -> [a]
forall a. [a] -> [a]
reverse ([a] -> [a]) -> ([a] -> [a]) -> [a] -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
take Int
5 ([a] -> [a]) -> ([a] -> [a]) -> [a] -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> [a]
forall a. [a] -> [a]
reverse) [a]
s1) [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ [a]
s2
sampleSteps :: [a]
sampleSteps = [a
1,a
2,a
5] [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ [a]
sampleSteps1
sampleSteps1 :: [a]
sampleSteps1 = [a
10,a
20,a
25,a
50] [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ (a -> a) -> [a] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map (a -> a -> a
forall a. Num a => a -> a -> a
*a
10) [a]
sampleSteps1
steps :: a -> (a, b) -> [a]
steps a
size (a
minV,b
maxV) = (a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<a
b) [a
a,a
aa -> a -> a
forall a. Num a => a -> a -> a
+a
size..] [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ [a
b]
where
a :: a
a = (a -> a
forall a b. (RealFrac a, Integral b) => a -> b
floor (a
minV a -> a -> a
forall a. Fractional a => a -> a -> a
/ a -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
size)) a -> a -> a
forall a. Num a => a -> a -> a
* a
size
b :: a
b = (b -> a
forall a b. (RealFrac a, Integral b) => a -> b
ceiling (b
maxV b -> b -> b
forall a. Fractional a => a -> a -> a
/ a -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
size)) a -> a -> a
forall a. Num a => a -> a -> a
* a
size