Safe Haskell | None |
---|---|
Language | Haskell2010 |
Chart.Types
Synopsis
- data Chart a = Chart {
- annotation :: Annotation
- spots :: [Spot a]
- type Chartable a = (Real a, Fractional a, RealFrac a, RealFloat a, Floating a)
- data Annotation
- annotationText :: Annotation -> Text
- data RectStyle = RectStyle Double Colour 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 Orientation
- fromOrientation :: IsString s => Orientation -> s
- toOrientation :: (Eq s, IsString s) => s -> Orientation
- data Spot a
- toRect :: Spot a -> Rect a
- toPoint :: (Ord a, Fractional a) => Spot a -> Point a
- pattern SR :: a -> a -> a -> a -> Spot a
- pattern SP :: a -> a -> Spot 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 FormatN
- defaultFormatN :: FormatN
Documentation
A Chart
consists of
- a list of spots on the xy-plane, and
- specific style of representation for each spot (an Annotation)
Constructors
Chart | |
Fields
|
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.0.3-7exTAOGVqFp4RtiGXqy9zP" 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]))) |
type Chartable a = (Real a, Fractional a, RealFrac a, RealFloat a, Floating a) Source #
the aspects a number needs to be to form the data for a chart
data Annotation Source #
a piece of chart structure | The use of #rowName with Annotation doesn't seem to mesh well with polymorphism, so a switch to concrete types (which fit it with svg-tree methods) occurs at this layer, and the underlying ADTs use a lot of Doubles
Constructors
RectA RectStyle | |
TextA TextStyle [Text] | |
GlyphA GlyphStyle | |
LineA LineStyle | |
BlankA | |
PixelA PixelStyle |
Instances
annotationText :: Annotation -> Text Source #
Rectangle styling
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.0.3-7exTAOGVqFp4RtiGXqy9zP" 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
Text styling
Constructors
TextStyle | |
Instances
defaultTextStyle :: TextStyle Source #
the offical text style
Constructors
AnchorMiddle | |
AnchorStart | |
AnchorEnd |
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.0.3-7exTAOGVqFp4RtiGXqy9zP" 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 #
data GlyphStyle Source #
Glyph styling
Constructors
GlyphStyle | |
Instances
defaultGlyphStyle :: GlyphStyle Source #
the offical circle style
data GlyphShape Source #
glyph shapes
Constructors
Instances
glyphText :: GlyphShape -> Text Source #
line style
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.0.3-7exTAOGVqFp4RtiGXqy9zP" 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 #
Constructors
PixelStyle | |
Fields
|
Instances
data Orientation Source #
Verticle or Horizontal
Instances
Eq Orientation Source # | |
Defined in Chart.Types | |
Show Orientation Source # | |
Defined in Chart.Types Methods showsPrec :: Int -> Orientation -> ShowS # show :: Orientation -> String # showList :: [Orientation] -> ShowS # | |
Generic Orientation Source # | |
Defined in Chart.Types Associated Types type Rep Orientation :: Type -> Type # | |
type Rep Orientation Source # | |
fromOrientation :: IsString s => Orientation -> s Source #
toOrientation :: (Eq s, IsString s) => s -> Orientation Source #
unification of a point and rect on the plane
Constructors
ManualAspect Double | |
ChartAspect |
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.0.3-7exTAOGVqFp4RtiGXqy9zP" 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 #
data EscapeText Source #
Constructors
EscapeText | |
NoEscapeText |
Instances
Eq EscapeText Source # | |
Defined in Chart.Types | |
Show EscapeText Source # | |
Defined in Chart.Types Methods showsPrec :: Int -> EscapeText -> ShowS # show :: EscapeText -> String # showList :: [EscapeText] -> ShowS # | |
Generic EscapeText Source # | |
Defined in Chart.Types Associated Types type Rep EscapeText :: Type -> Type # | |
type Rep EscapeText Source # | |
data CssOptions Source #
Constructors
UseCssCrisp | |
NoCssOptions |
Instances
Eq CssOptions Source # | |
Defined in Chart.Types | |
Show CssOptions Source # | |
Defined in Chart.Types Methods showsPrec :: Int -> CssOptions -> ShowS # show :: CssOptions -> String # showList :: [CssOptions] -> ShowS # | |
Generic CssOptions Source # | |
Defined in Chart.Types Associated Types type Rep CssOptions :: Type -> Type # | |
type Rep CssOptions Source # | |
data ScaleCharts Source #
Constructors
ScaleCharts | |
NoScaleCharts |
Instances
Eq ScaleCharts Source # | |
Defined in Chart.Types | |
Show ScaleCharts Source # | |
Defined in Chart.Types Methods showsPrec :: Int -> ScaleCharts -> ShowS # show :: ScaleCharts -> String # showList :: [ScaleCharts] -> ShowS # | |
Generic ScaleCharts Source # | |
Defined in Chart.Types Associated Types type Rep ScaleCharts :: Type -> Type # | |
type Rep ScaleCharts Source # | |
data SvgOptions Source #
Top-level SVG options.
Constructors
SvgOptions | |
Fields
|
Instances
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.0.3-7exTAOGVqFp4RtiGXqy9zP" 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))))) |
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.
Constructors
HudOptions | |
Fields
|
Instances
data AxisOptions Source #
Constructors
AxisOptions | |
Instances
Eq AxisOptions Source # | |
Defined in Chart.Types | |
Show AxisOptions Source # | |
Defined in Chart.Types Methods showsPrec :: Int -> AxisOptions -> ShowS # show :: AxisOptions -> String # showList :: [AxisOptions] -> ShowS # | |
Generic AxisOptions Source # | |
Defined in Chart.Types Associated Types type Rep AxisOptions :: Type -> Type # | |
type Rep AxisOptions Source # | |
Defined in Chart.Types type Rep AxisOptions = D1 (MetaData "AxisOptions" "Chart.Types" "chart-svg-0.0.3-7exTAOGVqFp4RtiGXqy9zP" False) (C1 (MetaCons "AxisOptions" PrefixI True) ((S1 (MetaSel (Just "abar") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bar)) :*: S1 (MetaSel (Just "adjust") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Adjustments))) :*: (S1 (MetaSel (Just "atick") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Tick) :*: S1 (MetaSel (Just "place") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Place)))) |
Placement of elements around (what is implicity but maybe shouldn't just be) a rectangular canvas
Constructors
PlaceLeft | |
PlaceRight | |
PlaceTop | |
PlaceBottom | |
PlaceAbsolute (Point Double) |
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.0.3-7exTAOGVqFp4RtiGXqy9zP" 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)))))) |
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.0.3-7exTAOGVqFp4RtiGXqy9zP" 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 #
Options for titles. Defaults to center aligned, and placed at Top of the hud
Constructors
Title | |
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.0.3-7exTAOGVqFp4RtiGXqy9zP" 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 #
Constructors
Tick | |
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.0.3-7exTAOGVqFp4RtiGXqy9zP" 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)))))) |
defaultTick :: Tick Source #
Style of tick marks on an axis.
Constructors
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
tickStyleText :: TickStyle -> Text Source #
data TickExtend Source #
Constructors
TickExtend | |
NoTickExtend |
Instances
Eq TickExtend Source # | |
Defined in Chart.Types | |
Show TickExtend Source # | |
Defined in Chart.Types Methods showsPrec :: Int -> TickExtend -> ShowS # show :: TickExtend -> String # showList :: [TickExtend] -> ShowS # | |
Generic TickExtend Source # | |
Defined in Chart.Types Associated Types type Rep TickExtend :: Type -> Type # | |
type Rep TickExtend Source # | |
data Adjustments Source #
options for prettifying axis decorations
Constructors
Adjustments | |
Fields
|
Instances
Eq Adjustments Source # | |
Defined in Chart.Types | |
Show Adjustments Source # | |
Defined in Chart.Types Methods showsPrec :: Int -> Adjustments -> ShowS # show :: Adjustments -> String # showList :: [Adjustments] -> ShowS # | |
Generic Adjustments Source # | |
Defined in Chart.Types Associated Types type Rep Adjustments :: Type -> Type # | |
type Rep Adjustments Source # | |
Defined in Chart.Types type Rep Adjustments = D1 (MetaData "Adjustments" "Chart.Types" "chart-svg-0.0.3-7exTAOGVqFp4RtiGXqy9zP" False) (C1 (MetaCons "Adjustments" PrefixI True) ((S1 (MetaSel (Just "maxXRatio") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double) :*: S1 (MetaSel (Just "maxYRatio") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)) :*: (S1 (MetaSel (Just "angledRatio") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double) :*: S1 (MetaSel (Just "allowDiagonal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))) |
data LegendOptions Source #
Legend options
Constructors
LegendOptions | |
Instances
Constructors
FormatFixed Int | |
FormatComma Int | |
FormatExpt Int | |
FormatDollar | |
FormatPercent Int | |
FormatNone |
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.0.3-7exTAOGVqFp4RtiGXqy9zP" 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)))) |