module Graphics.Gnuplot.Frame.OptionSet.Style (
fillSolid,
fillBorder,
fillBorderLineType,
) where
import qualified Graphics.Gnuplot.Private.FrameOptionSet as OptionSet
import qualified Graphics.Gnuplot.Private.FrameOption as Option
import qualified Graphics.Gnuplot.Private.Graph as Graph
import Graphics.Gnuplot.Private.FrameOptionSet (T, )
fillSolid :: Graph.C graph => T graph -> T graph
fillSolid :: T graph -> T graph
fillSolid =
T -> Bool -> T graph -> T graph
forall graph. T -> Bool -> T graph -> T graph
OptionSet.addBool T
Option.styleFillSolid Bool
True
fillBorder :: Graph.C graph => Bool -> T graph -> T graph
fillBorder :: Bool -> T graph -> T graph
fillBorder =
T -> Bool -> T graph -> T graph
forall graph. T -> Bool -> T graph -> T graph
OptionSet.addBool T
Option.styleFillBorder
fillBorderLineType :: Graph.C graph => Int -> T graph -> T graph
fillBorderLineType :: Int -> T graph -> T graph
fillBorderLineType Int
n =
T -> [String] -> T graph -> T graph
forall graph. T -> [String] -> T graph -> T graph
OptionSet.add T
Option.styleFillBorder [String
"border", Int -> String
forall a. Show a => a -> String
show Int
n]