{-# OPTIONS_GHC -fno-warn-orphans #-}
module Graphics.Rendering.Chart.Axis.Unit(
unitAxis,
) where
import Data.Default.Class
import Graphics.Rendering.Chart.Axis.Types
instance PlotValue () where
toValue :: () -> Double
toValue () = Double
0
fromValue :: Double -> ()
fromValue = () -> Double -> ()
forall a b. a -> b -> a
const ()
autoAxis :: AxisFn ()
autoAxis = AxisData () -> AxisFn ()
forall a b. a -> b -> a
const AxisData ()
unitAxis
unitAxis :: AxisData ()
unitAxis :: AxisData ()
unitAxis = AxisData :: forall x.
AxisVisibility
-> (Range -> x -> Double)
-> (Range -> Double -> x)
-> [(x, Double)]
-> [[(x, String)]]
-> [x]
-> AxisData x
AxisData {
_axis_visibility :: AxisVisibility
_axis_visibility = AxisVisibility
forall a. Default a => a
def
{ _axis_show_ticks :: Bool
_axis_show_ticks = Bool
False
, _axis_show_labels :: Bool
_axis_show_labels = Bool
False
},
_axis_viewport :: Range -> () -> Double
_axis_viewport = \(Double
x0,Double
x1) ()
_ -> (Double
x0Double -> Double -> Double
forall a. Num a => a -> a -> a
+Double
x1)Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
2,
_axis_tropweiv :: Range -> Double -> ()
_axis_tropweiv = \Range
_ Double
_ -> (),
_axis_ticks :: [((), Double)]
_axis_ticks = [((), Double
0)],
_axis_labels :: [[((), String)]]
_axis_labels = [[((), String
"")]],
_axis_grid :: [()]
_axis_grid = []
}