module Graphics.Gnuplot.Frame.OptionSet.Histogram (
   clustered,
   clusteredGap,
   errorbars,
   errorbarsGap,
   errorbarsGapLineWidth,
   rowstacked,
   columnstacked,
   ) where

import qualified Graphics.Gnuplot.Graph.TwoDimensional as Graph2D

import qualified Graphics.Gnuplot.Private.FrameOptionSet as OptionSet
import qualified Graphics.Gnuplot.Private.FrameOption as Option

import qualified Graphics.Gnuplot.Value.Atom as Atom

import Graphics.Gnuplot.Private.FrameOptionSet (T, )


clustered ::
   (Atom.C x, Atom.C y) =>
   T (Graph2D.T x y) -> T (Graph2D.T x y)
clustered :: T (T x y) -> T (T x y)
clustered =
   T -> [String] -> T (T x y) -> T (T x y)
forall graph. T -> [String] -> T graph -> T graph
OptionSet.add T
Option.styleHistogram [String
"clustered"]

clusteredGap ::
   (Atom.C x, Atom.C y) =>
   Double -> T (Graph2D.T x y) -> T (Graph2D.T x y)
clusteredGap :: Double -> T (T x y) -> T (T x y)
clusteredGap Double
gapSize =
   T -> [String] -> T (T x y) -> T (T x y)
forall graph. T -> [String] -> T graph -> T graph
OptionSet.add T
Option.styleHistogram [String
"clustered", String
"gap", Double -> String
forall a. Show a => a -> String
show Double
gapSize]

errorbars ::
   (Atom.C x, Atom.C y) =>
   T (Graph2D.T x y) -> T (Graph2D.T x y)
errorbars :: T (T x y) -> T (T x y)
errorbars =
   T -> [String] -> T (T x y) -> T (T x y)
forall graph. T -> [String] -> T graph -> T graph
OptionSet.add T
Option.styleHistogram [String
"errorbars"]

errorbarsGap ::
   (Atom.C x, Atom.C y) =>
   Double -> T (Graph2D.T x y) -> T (Graph2D.T x y)
errorbarsGap :: Double -> T (T x y) -> T (T x y)
errorbarsGap Double
gapSize =
   T -> [String] -> T (T x y) -> T (T x y)
forall graph. T -> [String] -> T graph -> T graph
OptionSet.add T
Option.styleHistogram [String
"errorbars", String
"gap", Double -> String
forall a. Show a => a -> String
show Double
gapSize]

errorbarsGapLineWidth ::
   (Atom.C x, Atom.C y) =>
   Double -> Double -> T (Graph2D.T x y) -> T (Graph2D.T x y)
errorbarsGapLineWidth :: Double -> Double -> T (T x y) -> T (T x y)
errorbarsGapLineWidth Double
gapSize Double
width =
   T -> [String] -> T (T x y) -> T (T x y)
forall graph. T -> [String] -> T graph -> T graph
OptionSet.add T
Option.styleHistogram [String
"errorbars", String
"gap", Double -> String
forall a. Show a => a -> String
show Double
gapSize, Double -> String
forall a. Show a => a -> String
show Double
width]

rowstacked ::
   (Atom.C x, Atom.C y) =>
   T (Graph2D.T x y) -> T (Graph2D.T x y)
rowstacked :: T (T x y) -> T (T x y)
rowstacked =
   T -> [String] -> T (T x y) -> T (T x y)
forall graph. T -> [String] -> T graph -> T graph
OptionSet.add T
Option.styleHistogram [String
"rowstacked"]

columnstacked ::
   (Atom.C x, Atom.C y) =>
   T (Graph2D.T x y) -> T (Graph2D.T x y)
columnstacked :: T (T x y) -> T (T x y)
columnstacked =
   T -> [String] -> T (T x y) -> T (T x y)
forall graph. T -> [String] -> T graph -> T graph
OptionSet.add T
Option.styleHistogram [String
"columnstacked"]