Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Chart a = Chart {
- annotation :: Annotation
- spots :: [Spot a]
- data Annotation
- annotationText :: Annotation -> Text
- blank :: [Chart Double]
- data RectStyle = RectStyle {
- borderSize :: Double
- borderColor :: Colour
- color :: Colour
- defaultRectStyle :: RectStyle
- blob :: Colour -> RectStyle
- clear :: RectStyle
- border :: Double -> Colour -> RectStyle
- data TextStyle = TextStyle {}
- defaultTextStyle :: TextStyle
- data Anchor
- fromAnchor :: IsString s => Anchor -> s
- toAnchor :: (Eq s, IsString s) => s -> Anchor
- data GlyphStyle = GlyphStyle {}
- defaultGlyphStyle :: GlyphStyle
- data GlyphShape
- glyphText :: GlyphShape -> Text
- data LineStyle = LineStyle {}
- defaultLineStyle :: LineStyle
- data PixelStyle = PixelStyle {}
- defaultPixelStyle :: PixelStyle
- data Direction
- fromDirection :: IsString s => Direction -> s
- toDirection :: (Eq s, IsString s) => s -> Direction
- data Spot a
- toRect :: Spot a -> Rect a
- toPoint :: (Ord a, Fractional a) => Spot a -> Point a
- padRect :: Num a => a -> Rect a -> Rect a
- data SvgAspect
- toSvgAspect :: (Eq s, IsString s) => s -> Double -> SvgAspect
- fromSvgAspect :: IsString s => SvgAspect -> s
- data EscapeText
- data CssOptions
- data ScaleCharts
- data SvgOptions = SvgOptions {}
- defaultSvgOptions :: SvgOptions
- defaultSvgFrame :: RectStyle
- data ChartDims a = ChartDims {}
- newtype HudT m a = Hud {}
- type Hud = HudT Identity
- data HudOptions = HudOptions {
- hudCanvas :: Maybe RectStyle
- hudTitles :: [Title]
- hudAxes :: [AxisOptions]
- hudLegend :: Maybe (LegendOptions, [(Annotation, Text)])
- defaultHudOptions :: HudOptions
- defaultCanvas :: RectStyle
- data AxisOptions = AxisOptions {}
- defaultAxisOptions :: AxisOptions
- data Place
- placeText :: Place -> Text
- data Bar = Bar {}
- defaultBar :: Bar
- data Title = Title {}
- defaultTitle :: Text -> Title
- data Tick = Tick {}
- defaultGlyphTick :: GlyphStyle
- defaultTextTick :: TextStyle
- defaultLineTick :: LineStyle
- defaultTick :: Tick
- data TickStyle
- = TickNone
- | TickLabels [Text]
- | TickRound FormatN Int TickExtend
- | TickExact FormatN Int
- | TickPlaced [(Double, Text)]
- defaultTickStyle :: TickStyle
- tickStyleText :: TickStyle -> Text
- data TickExtend
- data Adjustments = Adjustments {
- maxXRatio :: Double
- maxYRatio :: Double
- angledRatio :: Double
- allowDiagonal :: Bool
- defaultAdjustments :: Adjustments
- data LegendOptions = LegendOptions {}
- defaultLegendOptions :: LegendOptions
- data Colour
- pattern Colour :: Double -> Double -> Double -> Double -> Colour
- opac :: Colour -> Double
- setOpac :: Double -> Colour -> Colour
- fromRGB :: Color RGB Double -> Double -> Colour
- hex :: Colour -> Text
- palette :: [Color RGB Double]
- palette1 :: [Colour]
- blend :: Double -> Colour -> Colour -> Colour
- toHex :: Colour -> Text
- fromHex :: Text -> Either Text (Color RGB Double)
- unsafeFromHex :: Text -> Color RGB Double
- grayscale :: Double -> Color RGB Double
- colorText :: Colour
- transparent :: Colour
- black :: Colour
- white :: Colour
- module Graphics.Color.Model
- data FormatN
- defaultFormatN :: FormatN
- fromFormatN :: IsString s => FormatN -> s
- toFormatN :: (Eq s, IsString s) => s -> Int -> FormatN
- fixed :: Int -> Double -> Text
- comma :: Int -> Double -> Text
- expt :: Int -> Double -> Text
- dollar :: Double -> Text
- formatN :: FormatN -> Double -> Text
- precision :: (Int -> Double -> Text) -> Int -> [Double] -> [Text]
- formatNs :: FormatN -> [Double] -> [Text]
- projectTo :: (Ord a, Fractional a) => Rect a -> [Spot a] -> [Spot a]
- projectSpots :: (Ord a, Fractional a) => Rect a -> [Chart a] -> [Chart a]
- projectSpotsWith :: (Ord a, Fractional a) => Rect a -> Rect a -> [Chart a] -> [Chart a]
- dataBox :: Ord a => [Chart a] -> Maybe (Rect a)
- toAspect :: (Divisive a, Subtractive a) => Rect a -> a
- scaleAnn :: Double -> Annotation -> Annotation
- defRect :: Fractional a => Maybe (Rect a) -> Rect a
- defRectS :: (Subtractive a, Eq a, FromRational a, Fractional a) => Maybe (Rect a) -> Rect a
- moveChart :: (Ord a, Fractional a) => Spot a -> [Chart a] -> [Chart a]
- runHudWith :: Rect Double -> Rect Double -> [Hud Double] -> [Chart Double] -> [Chart Double]
- runHud :: Rect Double -> [Hud Double] -> [Chart Double] -> [Chart Double]
- makeHud :: Rect Double -> HudOptions -> ([Hud Double], [Chart Double])
- freezeTicks :: Place -> Rect Double -> TickStyle -> (TickStyle, Maybe (Rect Double))
- flipAxis :: AxisOptions -> AxisOptions
- canvas :: Monad m => RectStyle -> HudT m Double
- title :: Monad m => Title -> HudT m Double
- tick :: Monad m => Place -> Tick -> HudT m Double
- adjustTick :: Adjustments -> Rect Double -> Rect Double -> Place -> Tick -> Tick
- makeTickDates :: PosDiscontinuous -> Maybe Text -> Int -> [UTCTime] -> [(Int, Text)]
- makeTickDatesContinuous :: PosDiscontinuous -> Maybe Text -> Int -> [UTCTime] -> [(Double, Text)]
- legendHud :: LegendOptions -> [Chart Double] -> Hud Double
- legendEntry :: LegendOptions -> Annotation -> Text -> (Chart Double, Chart Double)
- legendChart :: [(Annotation, Text)] -> LegendOptions -> [Chart Double]
- legendFromChart :: [Text] -> [Chart Double] -> [(Annotation, Text)]
- svg :: Chart Double -> Html ()
- svgt :: Chart Double -> (TextStyle, Text) -> Html ()
- chartDef :: Chart a -> [Html ()]
- chartDefs :: [Chart a] -> Html ()
- styleBox :: Chart Double -> Maybe (Rect Double)
- styleBoxes :: [Chart Double] -> Maybe (Rect Double)
- noStyleBoxes :: [Chart Double] -> Maybe (Rect Double)
- styleBoxText :: TextStyle -> Text -> Point Double -> Rect Double
- styleBoxGlyph :: GlyphStyle -> Rect Double
- padChart :: Double -> [Chart Double] -> [Chart Double]
- frameChart :: RectStyle -> Double -> [Chart Double] -> [Chart Double]
- hori :: Double -> [[Chart Double]] -> [Chart Double]
- vert :: Double -> [[Chart Double]] -> [Chart Double]
- stack :: Int -> Double -> [[Chart Double]] -> [Chart Double]
- addChartBox :: Chart Double -> Rect Double -> Rect Double
- addChartBoxes :: [Chart Double] -> Rect Double -> Rect Double
Documentation
A Chart
consists of
- a list of spots on the xy-plane, and
- specific style of representation for each spot.
Chart | |
|
Instances
Eq a => Eq (Chart a) Source # | |
Show a => Show (Chart a) Source # | |
Generic (Chart a) Source # | |
type Rep (Chart a) Source # | |
Defined in Chart.Types type Rep (Chart a) = D1 (MetaData "Chart" "Chart.Types" "chart-svg-0.1.0-CZA6O3dBQljBPs6qs8s7lY" False) (C1 (MetaCons "Chart" PrefixI True) (S1 (MetaSel (Just "annotation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Annotation) :*: S1 (MetaSel (Just "spots") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Spot a]))) |
data Annotation Source #
Manifestation of the data on a screen.
Instances
annotationText :: Annotation -> Text Source #
Rectangle styling
>>>
defaultRectStyle
RectStyle {borderSize = 1.0e-2, borderColor = RGBA 0.12 0.47 0.71 0.80, color = RGBA 0.12 0.47 0.71 0.30}
writeCharts "other/unit.svg" [Chart (RectA defaultRectStyle) [SpotRect (unitRect::Rect Double)]]
RectStyle | |
|
Instances
Eq RectStyle Source # | |
Show RectStyle Source # | |
Generic RectStyle Source # | |
type Rep RectStyle Source # | |
Defined in Chart.Types type Rep RectStyle = D1 (MetaData "RectStyle" "Chart.Types" "chart-svg-0.1.0-CZA6O3dBQljBPs6qs8s7lY" False) (C1 (MetaCons "RectStyle" PrefixI True) (S1 (MetaSel (Just "borderSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double) :*: (S1 (MetaSel (Just "borderColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Colour) :*: S1 (MetaSel (Just "color") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Colour)))) |
defaultRectStyle :: RectStyle Source #
the style
blob :: Colour -> RectStyle Source #
solid rectangle, no border
>>>
blob black
RectStyle {borderSize = 0.0, borderColor = RGBA 0.00 0.00 0.00 0.00, color = RGBA 0.00 0.00 0.00 1.00}
transparent rect
>>>
clear
RectStyle {borderSize = 0.0, borderColor = RGBA 0.00 0.00 0.00 0.00, color = RGBA 0.00 0.00 0.00 0.00}
border :: Double -> Colour -> RectStyle Source #
transparent rectangle, with border
>>>
border 0.01 transparent
RectStyle {borderSize = 1.0e-2, borderColor = RGBA 0.00 0.00 0.00 0.00, color = RGBA 0.00 0.00 0.00 0.00}
Text styling
>>>
defaultTextStyle
TextStyle {size = 8.0e-2, color = RGBA 0.20 0.20 0.20 1.00, anchor = AnchorMiddle, hsize = 0.5, vsize = 1.45, nudge1 = -0.2, rotation = Nothing, translate = Nothing, hasMathjax = False}
>>>
let t = zipWith (\x y -> Chart (TextA (defaultTextStyle & (#size .~ (0.05 :: Double))) [x]) [SpotPoint y]) (fmap Text.singleton ['a' .. 'y']) [Point (sin (x * 0.1)) x | x <- [0 .. 25]]
writeCharts "other/text.svg" t
Instances
defaultTextStyle :: TextStyle Source #
the offical text style
position anchor
Instances
Eq Anchor Source # | |
Show Anchor Source # | |
Generic Anchor Source # | |
type Rep Anchor Source # | |
Defined in Chart.Types type Rep Anchor = D1 (MetaData "Anchor" "Chart.Types" "chart-svg-0.1.0-CZA6O3dBQljBPs6qs8s7lY" False) (C1 (MetaCons "AnchorMiddle" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "AnchorStart" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "AnchorEnd" PrefixI False) (U1 :: Type -> Type))) |
fromAnchor :: IsString s => Anchor -> s Source #
text
data GlyphStyle Source #
Glyph styling
>>>
defaultGlyphStyle
GlyphStyle {size = 3.0e-2, color = RGBA 0.65 0.81 0.89 0.30, borderColor = RGBA 0.12 0.47 0.71 0.80, borderSize = 3.0e-3, shape = SquareGlyph, rotation = Nothing, translate = Nothing}
Instances
defaultGlyphStyle :: GlyphStyle Source #
the offical glyph style
data GlyphShape Source #
glyph shapes
Instances
glyphText :: GlyphShape -> Text Source #
textifier
line style
>>>
defaultLineStyle
LineStyle {width = 1.2e-2, color = RGBA 0.65 0.81 0.89 0.30}
Instances
Eq LineStyle Source # | |
Show LineStyle Source # | |
Generic LineStyle Source # | |
type Rep LineStyle Source # | |
Defined in Chart.Types type Rep LineStyle = D1 (MetaData "LineStyle" "Chart.Types" "chart-svg-0.1.0-CZA6O3dBQljBPs6qs8s7lY" False) (C1 (MetaCons "LineStyle" PrefixI True) (S1 (MetaSel (Just "width") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double) :*: S1 (MetaSel (Just "color") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Colour))) |
defaultLineStyle :: LineStyle Source #
the official default line style
data PixelStyle Source #
A pixel chart is a specialization of a RectA
chart
>>>
defaultPixelStyle
PixelStyle {pixelColorMin = RGBA 0.65 0.81 0.89 1.00, pixelColorMax = RGBA 0.12 0.47 0.71 1.00, pixelGradient = 1.5707963267948966, pixelRectStyle = RectStyle {borderSize = 0.0, borderColor = RGBA 0.00 0.00 0.00 0.00, color = RGBA 0.00 0.00 0.00 1.00}, pixelTextureId = "pixel"}
PixelStyle | |
|
Instances
defaultPixelStyle :: PixelStyle Source #
The official pixel style.
Verticle or Horizontal
fromDirection :: IsString s => Direction -> s Source #
textifier
unification of a point and rect on the plane
The x-y ratio of the viewing box
Instances
Eq SvgAspect Source # | |
Show SvgAspect Source # | |
Generic SvgAspect Source # | |
type Rep SvgAspect Source # | |
Defined in Chart.Types type Rep SvgAspect = D1 (MetaData "SvgAspect" "Chart.Types" "chart-svg-0.1.0-CZA6O3dBQljBPs6qs8s7lY" False) (C1 (MetaCons "ManualAspect" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)) :+: C1 (MetaCons "ChartAspect" PrefixI False) (U1 :: Type -> Type)) |
fromSvgAspect :: IsString s => SvgAspect -> s Source #
textifier
data EscapeText Source #
or html
Instances
Eq EscapeText Source # | |
Defined in Chart.Types (==) :: EscapeText -> EscapeText -> Bool # (/=) :: EscapeText -> EscapeText -> Bool # | |
Show EscapeText Source # | |
Defined in Chart.Types showsPrec :: Int -> EscapeText -> ShowS # show :: EscapeText -> String # showList :: [EscapeText] -> ShowS # | |
Generic EscapeText Source # | |
Defined in Chart.Types type Rep EscapeText :: Type -> Type # from :: EscapeText -> Rep EscapeText x # to :: Rep EscapeText x -> EscapeText # | |
type Rep EscapeText Source # | |
data CssOptions Source #
pixel chart helper
Instances
Eq CssOptions Source # | |
Defined in Chart.Types (==) :: CssOptions -> CssOptions -> Bool # (/=) :: CssOptions -> CssOptions -> Bool # | |
Show CssOptions Source # | |
Defined in Chart.Types showsPrec :: Int -> CssOptions -> ShowS # show :: CssOptions -> String # showList :: [CssOptions] -> ShowS # | |
Generic CssOptions Source # | |
Defined in Chart.Types type Rep CssOptions :: Type -> Type # from :: CssOptions -> Rep CssOptions x # to :: Rep CssOptions x -> CssOptions # | |
type Rep CssOptions Source # | |
data ScaleCharts Source #
turns off scaling. Usually not what you want.
Instances
Eq ScaleCharts Source # | |
Defined in Chart.Types (==) :: ScaleCharts -> ScaleCharts -> Bool # (/=) :: ScaleCharts -> ScaleCharts -> Bool # | |
Show ScaleCharts Source # | |
Defined in Chart.Types showsPrec :: Int -> ScaleCharts -> ShowS # show :: ScaleCharts -> String # showList :: [ScaleCharts] -> ShowS # | |
Generic ScaleCharts Source # | |
Defined in Chart.Types type Rep ScaleCharts :: Type -> Type # from :: ScaleCharts -> Rep ScaleCharts x # to :: Rep ScaleCharts x -> ScaleCharts # | |
type Rep ScaleCharts Source # | |
data SvgOptions Source #
Top-level SVG options.
>>>
defaultSvgOptions
SvgOptions {svgHeight = 300.0, outerPad = Just 2.0e-2, innerPad = Nothing, chartFrame = Nothing, escapeText = NoEscapeText, useCssCrisp = NoCssOptions, scaleCharts' = ScaleCharts, svgAspect = ManualAspect 1.5}
writeChartsWith "other/svgoptions.svg" (defaultSvgOptions & #svgAspect .~ ManualAspect 0.7) lines
SvgOptions | |
|
Instances
defaultSvgOptions :: SvgOptions Source #
The official svg options
defaultSvgFrame :: RectStyle Source #
frame style
In order to create huds, there are three main pieces of state that need to be kept track of:
- chartDim: the rectangular dimension of the physical representation of a chart on the screen so that new hud elements can be appended. Adding a hud piece tends to expand the chart dimension.
- canvasDim: the rectangular dimension of the canvas on which data will be represented. At times appending a hud element will cause the canvas dimension to shift.
- dataDim: the rectangular dimension of the data being represented. Adding hud elements can cause this to change.
Instances
Eq a => Eq (ChartDims a) Source # | |
Show a => Show (ChartDims a) Source # | |
Generic (ChartDims a) Source # | |
type Rep (ChartDims a) Source # | |
Defined in Chart.Types type Rep (ChartDims a) = D1 (MetaData "ChartDims" "Chart.Types" "chart-svg-0.1.0-CZA6O3dBQljBPs6qs8s7lY" False) (C1 (MetaCons "ChartDims" PrefixI True) (S1 (MetaSel (Just "chartDim") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Rect a)) :*: (S1 (MetaSel (Just "canvasDim") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Rect a)) :*: S1 (MetaSel (Just "dataDim") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Rect a))))) |
Hud monad transformer
data HudOptions Source #
Practically, the configuration of a Hud is going to be in decimals, typed into config files and the like, and so we concrete at the configuration level, and settle on doubles for specifying the geomtry of hud elements.
writeHudOptionsChart "other/hud.svg" defaultSvgOptions defaultHudOptions [] []
HudOptions | |
|
Instances
defaultHudOptions :: HudOptions Source #
The official hud options.
defaultCanvas :: RectStyle Source #
The official hud canvas
data AxisOptions Source #
axis options
Instances
defaultAxisOptions :: AxisOptions Source #
The official axis
Placement of elements around (what is implicity but maybe shouldn't just be) a rectangular canvas
Instances
Eq Place Source # | |
Show Place Source # | |
Generic Place Source # | |
type Rep Place Source # | |
Defined in Chart.Types type Rep Place = D1 (MetaData "Place" "Chart.Types" "chart-svg-0.1.0-CZA6O3dBQljBPs6qs8s7lY" False) ((C1 (MetaCons "PlaceLeft" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PlaceRight" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "PlaceTop" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "PlaceBottom" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PlaceAbsolute" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Point Double)))))) |
The bar on an axis representing the x or y plane.
>>>
defaultBar
Bar {rstyle = RectStyle {borderSize = 0.0, borderColor = RGBA 0.50 0.50 0.50 1.00, color = RGBA 0.50 0.50 0.50 1.00}, wid = 5.0e-3, buff = 1.0e-2}
Instances
Eq Bar Source # | |
Show Bar Source # | |
Generic Bar Source # | |
type Rep Bar Source # | |
Defined in Chart.Types type Rep Bar = D1 (MetaData "Bar" "Chart.Types" "chart-svg-0.1.0-CZA6O3dBQljBPs6qs8s7lY" False) (C1 (MetaCons "Bar" PrefixI True) (S1 (MetaSel (Just "rstyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RectStyle) :*: (S1 (MetaSel (Just "wid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double) :*: S1 (MetaSel (Just "buff") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)))) |
defaultBar :: Bar Source #
The official axis bar
Options for titles. Defaults to center aligned, and placed at Top of the hud
Instances
Eq Title Source # | |
Show Title Source # | |
Generic Title Source # | |
type Rep Title Source # | |
Defined in Chart.Types type Rep Title = D1 (MetaData "Title" "Chart.Types" "chart-svg-0.1.0-CZA6O3dBQljBPs6qs8s7lY" False) (C1 (MetaCons "Title" PrefixI True) ((S1 (MetaSel (Just "text") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "style") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TextStyle)) :*: (S1 (MetaSel (Just "place") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Place) :*: (S1 (MetaSel (Just "anchor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Anchor) :*: S1 (MetaSel (Just "buff") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double))))) |
defaultTitle :: Text -> Title Source #
The official hud title
xy coordinate markings
>>>
defaultTick
Tick {tstyle = TickRound (FormatComma 0) 8 TickExtend, gtick = Just (GlyphStyle {size = 3.0e-2, color = RGBA 0.50 0.50 0.50 1.00, borderColor = RGBA 0.50 0.50 0.50 1.00, borderSize = 5.0e-3, shape = VLineGlyph 5.0e-3, rotation = Nothing, translate = Nothing},1.25e-2), ttick = Just (TextStyle {size = 5.0e-2, color = RGBA 0.50 0.50 0.50 1.00, anchor = AnchorMiddle, hsize = 0.5, vsize = 1.45, nudge1 = -0.2, rotation = Nothing, translate = Nothing, hasMathjax = False},1.5e-2), ltick = Just (LineStyle {width = 5.0e-3, color = RGBA 0.50 0.50 0.50 0.05},0.0)}
Instances
Eq Tick Source # | |
Show Tick Source # | |
Generic Tick Source # | |
type Rep Tick Source # | |
Defined in Chart.Types type Rep Tick = D1 (MetaData "Tick" "Chart.Types" "chart-svg-0.1.0-CZA6O3dBQljBPs6qs8s7lY" False) (C1 (MetaCons "Tick" PrefixI True) ((S1 (MetaSel (Just "tstyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TickStyle) :*: S1 (MetaSel (Just "gtick") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (GlyphStyle, Double)))) :*: (S1 (MetaSel (Just "ttick") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (TextStyle, Double))) :*: S1 (MetaSel (Just "ltick") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (LineStyle, Double)))))) |
defaultGlyphTick :: GlyphStyle Source #
The official glyph tick
defaultTextTick :: TextStyle Source #
The official text tick
defaultLineTick :: LineStyle Source #
The official line tick
defaultTick :: Tick Source #
The official tick
Style of tick marks on an axis.
TickNone | no ticks on axis |
TickLabels [Text] | specific labels (equidistant placement) |
TickRound FormatN Int TickExtend | sensibly rounded ticks, a guide to how many, and whether to extend beyond the data bounding box |
TickExact FormatN Int | exactly n equally spaced ticks |
TickPlaced [(Double, Text)] | specific labels and placement |
Instances
defaultTickStyle :: TickStyle Source #
The official tick style
tickStyleText :: TickStyle -> Text Source #
textifier
data TickExtend Source #
Whether Ticks are allowed to extend the data range
Instances
Eq TickExtend Source # | |
Defined in Chart.Types (==) :: TickExtend -> TickExtend -> Bool # (/=) :: TickExtend -> TickExtend -> Bool # | |
Show TickExtend Source # | |
Defined in Chart.Types showsPrec :: Int -> TickExtend -> ShowS # show :: TickExtend -> String # showList :: [TickExtend] -> ShowS # | |
Generic TickExtend Source # | |
Defined in Chart.Types type Rep TickExtend :: Type -> Type # from :: TickExtend -> Rep TickExtend x # to :: Rep TickExtend x -> TickExtend # | |
type Rep TickExtend Source # | |
data Adjustments Source #
options for prettifying axis decorations
>>>
defaultAdjustments
Adjustments {maxXRatio = 8.0e-2, maxYRatio = 6.0e-2, angledRatio = 0.12, allowDiagonal = True}
Adjustments | |
|
Instances
defaultAdjustments :: Adjustments Source #
The official hud adjustments.
data LegendOptions Source #
Legend options
>>>
defaultLegendOptions
LegendOptions {lsize = 0.1, vgap = 0.2, hgap = 0.1, ltext = TextStyle {size = 8.0e-2, color = RGBA 0.20 0.20 0.20 1.00, anchor = AnchorMiddle, hsize = 0.5, vsize = 1.45, nudge1 = -0.2, rotation = Nothing, translate = Nothing, hasMathjax = False}, lmax = 10, innerPad = 0.1, outerPad = 0.1, legendFrame = Just (RectStyle {borderSize = 2.0e-2, borderColor = RGBA 0.50 0.50 0.50 1.00, color = RGBA 1.00 1.00 1.00 1.00}), lplace = PlaceBottom, lscale = 0.2}
Instances
defaultLegendOptions :: LegendOptions Source #
The official legend options
snatching Colour as the library color representation.
transparent :: Colour Source #
re-exports
module Graphics.Color.Model
Number formatting options.
>>>
defaultFormatN
FormatComma 2
Instances
Eq FormatN Source # | |
Show FormatN Source # | |
Generic FormatN Source # | |
type Rep FormatN Source # | |
Defined in Chart.Types type Rep FormatN = D1 (MetaData "FormatN" "Chart.Types" "chart-svg-0.1.0-CZA6O3dBQljBPs6qs8s7lY" False) ((C1 (MetaCons "FormatFixed" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: (C1 (MetaCons "FormatComma" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: C1 (MetaCons "FormatExpt" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))) :+: (C1 (MetaCons "FormatDollar" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "FormatPercent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: C1 (MetaCons "FormatNone" PrefixI False) (U1 :: Type -> Type)))) |
defaultFormatN :: FormatN Source #
The official format
fromFormatN :: IsString s => FormatN -> s Source #
textifier
precision :: (Int -> Double -> Text) -> Int -> [Double] -> [Text] Source #
Provide formatted text for a list of numbers so that they are just distinguished. 'precision commas 2 ticks' means give the tick labels as much precision as is needed for them to be distinguished, but with at least 2 significant figures, and format Integers with commas.
projectTo :: (Ord a, Fractional a) => Rect a -> [Spot a] -> [Spot a] Source #
project a [Spot a] from it's folded space to the given area
>>>
projectTo unitRect (SpotPoint <$> zipWith Point [0..2] [0..2])
[SpotPoint Point -0.5 -0.5,SpotPoint Point 0.0 0.0,SpotPoint Point 0.5 0.5]
projectSpots :: (Ord a, Fractional a) => Rect a -> [Chart a] -> [Chart a] Source #
projectSpotsWith :: (Ord a, Fractional a) => Rect a -> Rect a -> [Chart a] -> [Chart a] Source #
scaleAnn :: Double -> Annotation -> Annotation Source #
defRectS :: (Subtractive a, Eq a, FromRational a, Fractional a) => Maybe (Rect a) -> Rect a Source #
:: Rect Double | initial canvas dimension |
-> Rect Double | initial data dimension |
-> [Hud Double] | huds to add |
-> [Chart Double] | underlying chart |
-> [Chart Double] | chart list |
combine huds and charts to form a new Chart using the supplied initial canvas and data dimensions. Note that chart data is transformed by this computation. used once in makePixelTick
runHud :: Rect Double -> [Hud Double] -> [Chart Double] -> [Chart Double] Source #
Combine huds and charts to form a new [Chart] using the supplied canvas and the actual data dimension. Note that the original chart data are transformed and irrevocably lost by this computation. used once in renderHudChart
makeHud :: Rect Double -> HudOptions -> ([Hud Double], [Chart Double]) Source #
Make huds from a HudOptions Some huds, such as the creation of tick values, can extend the data dimension of a chart, so we also return a blank chart with the new data dimension. The complexity internally is due to the creation of ticks and, specifically, gridSensible, which is not idempotent. As a result, a tick calculation that does extends the data area, can then lead to new tick values when applying TickRound etc.
flipAxis :: AxisOptions -> AxisOptions Source #
title :: Monad m => Title -> HudT m Double Source #
Add a title to a chart. The logic used to work out placement is flawed due to being able to freely specify text rotation. It works for specific rotations (Top, Bottom at 0, Left at 90, Right @ 270)
tick :: Monad m => Place -> Tick -> HudT m Double Source #
Create tick glyphs (marks), lines (grid) and text (labels)
adjustTick :: Adjustments -> Rect Double -> Rect Double -> Place -> Tick -> Tick Source #
adjust Tick for sane font sizes etc
makeTickDates :: PosDiscontinuous -> Maybe Text -> Int -> [UTCTime] -> [(Int, Text)] Source #
Convert a UTCTime list into sensible ticks, placed exactly
makeTickDatesContinuous :: PosDiscontinuous -> Maybe Text -> Int -> [UTCTime] -> [(Double, Text)] Source #
Convert a UTCTime list into sensible ticks, placed on the (0,1) space
legendEntry :: LegendOptions -> Annotation -> Text -> (Chart Double, Chart Double) Source #
legendChart :: [(Annotation, Text)] -> LegendOptions -> [Chart Double] Source #
legendFromChart :: [Text] -> [Chart Double] -> [(Annotation, Text)] Source #
styleBox :: Chart Double -> Maybe (Rect Double) Source #
the geometric dimensions of a Chart inclusive of style geometry
styleBoxes :: [Chart Double] -> Maybe (Rect Double) Source #
the extra geometric dimensions of a [Chart]
noStyleBoxes :: [Chart Double] -> Maybe (Rect Double) Source #
geometric dimensions of a [Chart] not including style
styleBoxText :: TextStyle -> Text -> Point Double -> Rect Double Source #
the extra area from text styling
styleBoxGlyph :: GlyphStyle -> Rect Double Source #
the extra area from glyph styling
padChart :: Double -> [Chart Double] -> [Chart Double] Source #
additively pad a [Chart]
>>>
padChart 0.1 [Chart (RectA defaultRectStyle) [SpotRect unitRect]]
[Chart {annotation = RectA (RectStyle {borderSize = 1.0e-2, borderColor = RGBA 0.12 0.47 0.71 0.80, color = RGBA 0.12 0.47 0.71 0.30}), spots = [SpotRect Rect -0.5 0.5 -0.5 0.5]},Chart {annotation = BlankA, spots = [SpotRect Rect -0.605 0.605 -0.605 0.605]}]
frameChart :: RectStyle -> Double -> [Chart Double] -> [Chart Double] Source #
overlay a frame on some charts with some additive padding between
>>>
frameChart defaultRectStyle 0.1 blank
[Chart {annotation = RectA (RectStyle {borderSize = 1.0e-2, borderColor = RGBA 0.12 0.47 0.71 0.80, color = RGBA 0.12 0.47 0.71 0.30}), spots = []},Chart {annotation = BlankA, spots = []}]