chart-svg-0.0.3: Charts in SVG

Safe HaskellNone
LanguageHaskell2010

Chart.Types

Synopsis

Documentation

data Chart a Source #

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 # 
Instance details

Defined in Chart.Types

Methods

(==) :: Chart a -> Chart a -> Bool #

(/=) :: Chart a -> Chart a -> Bool #

Show a => Show (Chart a) Source # 
Instance details

Defined in Chart.Types

Methods

showsPrec :: Int -> Chart a -> ShowS #

show :: Chart a -> String #

showList :: [Chart a] -> ShowS #

Generic (Chart a) Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep (Chart a) :: Type -> Type #

Methods

from :: Chart a -> Rep (Chart a) x #

to :: Rep (Chart a) x -> Chart a #

type Rep (Chart a) Source # 
Instance details

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

Instances
Eq Annotation Source # 
Instance details

Defined in Chart.Types

Show Annotation Source # 
Instance details

Defined in Chart.Types

Generic Annotation Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep Annotation :: Type -> Type #

type Rep Annotation Source # 
Instance details

Defined in Chart.Types

data RectStyle Source #

Rectangle styling

Instances
Eq RectStyle Source # 
Instance details

Defined in Chart.Types

Show RectStyle Source # 
Instance details

Defined in Chart.Types

Generic RectStyle Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep RectStyle :: Type -> Type #

type Rep RectStyle Source # 
Instance details

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))))

blob :: Colour -> RectStyle Source #

solid rectangle, no border

clear :: RectStyle Source #

clear and utrans rect

border :: Double -> Colour -> RectStyle Source #

transparent rectangle, with border

data TextStyle Source #

Text styling

Instances
Eq TextStyle Source # 
Instance details

Defined in Chart.Types

Show TextStyle Source # 
Instance details

Defined in Chart.Types

Generic TextStyle Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep TextStyle :: Type -> Type #

type Rep TextStyle Source # 
Instance details

Defined in Chart.Types

defaultTextStyle :: TextStyle Source #

the offical text style

data Anchor Source #

Instances
Eq Anchor Source # 
Instance details

Defined in Chart.Types

Methods

(==) :: Anchor -> Anchor -> Bool #

(/=) :: Anchor -> Anchor -> Bool #

Show Anchor Source # 
Instance details

Defined in Chart.Types

Generic Anchor Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep Anchor :: Type -> Type #

Methods

from :: Anchor -> Rep Anchor x #

to :: Rep Anchor x -> Anchor #

type Rep Anchor Source # 
Instance details

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)))

toAnchor :: (Eq s, IsString s) => s -> Anchor Source #

data GlyphStyle Source #

Glyph styling

Constructors

GlyphStyle 

Fields

Instances
Eq GlyphStyle Source # 
Instance details

Defined in Chart.Types

Show GlyphStyle Source # 
Instance details

Defined in Chart.Types

Generic GlyphStyle Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep GlyphStyle :: Type -> Type #

type Rep GlyphStyle Source # 
Instance details

Defined in Chart.Types

defaultGlyphStyle :: GlyphStyle Source #

the offical circle style

data GlyphShape Source #

glyph shapes

Instances
Eq GlyphShape Source # 
Instance details

Defined in Chart.Types

Show GlyphShape Source # 
Instance details

Defined in Chart.Types

Generic GlyphShape Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep GlyphShape :: Type -> Type #

type Rep GlyphShape Source # 
Instance details

Defined in Chart.Types

type Rep GlyphShape = D1 (MetaData "GlyphShape" "Chart.Types" "chart-svg-0.0.3-7exTAOGVqFp4RtiGXqy9zP" False) (((C1 (MetaCons "CircleGlyph" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SquareGlyph" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "EllipseGlyph" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)) :+: C1 (MetaCons "RectSharpGlyph" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)))) :+: ((C1 (MetaCons "RectRoundedGlyph" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double))) :+: C1 (MetaCons "TriangleGlyph" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Point Double)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Point Double)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Point Double))))) :+: (C1 (MetaCons "VLineGlyph" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)) :+: (C1 (MetaCons "HLineGlyph" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)) :+: C1 (MetaCons "PathGlyph" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))))

data LineStyle Source #

line style

Constructors

LineStyle 

Fields

Instances
Eq LineStyle Source # 
Instance details

Defined in Chart.Types

Show LineStyle Source # 
Instance details

Defined in Chart.Types

Generic LineStyle Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep LineStyle :: Type -> Type #

type Rep LineStyle Source # 
Instance details

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
Eq PixelStyle Source # 
Instance details

Defined in Chart.Types

Show PixelStyle Source # 
Instance details

Defined in Chart.Types

Generic PixelStyle Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep PixelStyle :: Type -> Type #

type Rep PixelStyle Source # 
Instance details

Defined in Chart.Types

data Orientation Source #

Verticle or Horizontal

Constructors

Vert 
Hori 
Instances
Eq Orientation Source # 
Instance details

Defined in Chart.Types

Show Orientation Source # 
Instance details

Defined in Chart.Types

Generic Orientation Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep Orientation :: Type -> Type #

type Rep Orientation Source # 
Instance details

Defined in Chart.Types

type Rep Orientation = D1 (MetaData "Orientation" "Chart.Types" "chart-svg-0.0.3-7exTAOGVqFp4RtiGXqy9zP" False) (C1 (MetaCons "Vert" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Hori" PrefixI False) (U1 :: Type -> Type))

data Spot a Source #

unification of a point and rect on the plane

Constructors

SpotPoint (Point a) 
SpotRect (Rect a) 
Instances
Functor Spot Source # 
Instance details

Defined in Chart.Types

Methods

fmap :: (a -> b) -> Spot a -> Spot b #

(<$) :: a -> Spot b -> Spot a #

Eq a => Eq (Spot a) Source # 
Instance details

Defined in Chart.Types

Methods

(==) :: Spot a -> Spot a -> Bool #

(/=) :: Spot a -> Spot a -> Bool #

(Ord a, Num a, Fractional a) => Num (Spot a) Source # 
Instance details

Defined in Chart.Types

Methods

(+) :: Spot a -> Spot a -> Spot a #

(-) :: Spot a -> Spot a -> Spot a #

(*) :: Spot a -> Spot a -> Spot a #

negate :: Spot a -> Spot a #

abs :: Spot a -> Spot a #

signum :: Spot a -> Spot a #

fromInteger :: Integer -> Spot a #

Show a => Show (Spot a) Source # 
Instance details

Defined in Chart.Types

Methods

showsPrec :: Int -> Spot a -> ShowS #

show :: Spot a -> String #

showList :: [Spot a] -> ShowS #

Ord a => Semigroup (Spot a) Source # 
Instance details

Defined in Chart.Types

Methods

(<>) :: Spot a -> Spot a -> Spot a #

sconcat :: NonEmpty (Spot a) -> Spot a #

stimes :: Integral b => b -> Spot a -> Spot a #

toRect :: Spot a -> Rect a Source #

Convert a spot to an Rect

toPoint :: (Ord a, Fractional a) => Spot a -> Point a Source #

Convert a spot to a Point

pattern SR :: a -> a -> a -> a -> Spot a Source #

pattern for SA lowerx upperx lowery uppery

pattern SP :: a -> a -> Spot a Source #

pattern for SP x y

padRect :: Num a => a -> Rect a -> Rect a Source #

additive padding

data SvgAspect Source #

Instances
Eq SvgAspect Source # 
Instance details

Defined in Chart.Types

Show SvgAspect Source # 
Instance details

Defined in Chart.Types

Generic SvgAspect Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep SvgAspect :: Type -> Type #

type Rep SvgAspect Source # 
Instance details

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))

data EscapeText Source #

Constructors

EscapeText 
NoEscapeText 
Instances
Eq EscapeText Source # 
Instance details

Defined in Chart.Types

Show EscapeText Source # 
Instance details

Defined in Chart.Types

Generic EscapeText Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep EscapeText :: Type -> Type #

type Rep EscapeText Source # 
Instance details

Defined in Chart.Types

type Rep EscapeText = D1 (MetaData "EscapeText" "Chart.Types" "chart-svg-0.0.3-7exTAOGVqFp4RtiGXqy9zP" False) (C1 (MetaCons "EscapeText" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NoEscapeText" PrefixI False) (U1 :: Type -> Type))

data CssOptions Source #

Constructors

UseCssCrisp 
NoCssOptions 
Instances
Eq CssOptions Source # 
Instance details

Defined in Chart.Types

Show CssOptions Source # 
Instance details

Defined in Chart.Types

Generic CssOptions Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep CssOptions :: Type -> Type #

type Rep CssOptions Source # 
Instance details

Defined in Chart.Types

type Rep CssOptions = D1 (MetaData "CssOptions" "Chart.Types" "chart-svg-0.0.3-7exTAOGVqFp4RtiGXqy9zP" False) (C1 (MetaCons "UseCssCrisp" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NoCssOptions" PrefixI False) (U1 :: Type -> Type))

data ScaleCharts Source #

Constructors

ScaleCharts 
NoScaleCharts 
Instances
Eq ScaleCharts Source # 
Instance details

Defined in Chart.Types

Show ScaleCharts Source # 
Instance details

Defined in Chart.Types

Generic ScaleCharts Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep ScaleCharts :: Type -> Type #

type Rep ScaleCharts Source # 
Instance details

Defined in Chart.Types

type Rep ScaleCharts = D1 (MetaData "ScaleCharts" "Chart.Types" "chart-svg-0.0.3-7exTAOGVqFp4RtiGXqy9zP" False) (C1 (MetaCons "ScaleCharts" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NoScaleCharts" PrefixI False) (U1 :: Type -> Type))

data SvgOptions Source #

Top-level SVG options.

Instances
Eq SvgOptions Source # 
Instance details

Defined in Chart.Types

Show SvgOptions Source # 
Instance details

Defined in Chart.Types

Generic SvgOptions Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep SvgOptions :: Type -> Type #

type Rep SvgOptions Source # 
Instance details

Defined in Chart.Types

data ChartDims a Source #

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.

Constructors

ChartDims 

Fields

Instances
Eq a => Eq (ChartDims a) Source # 
Instance details

Defined in Chart.Types

Methods

(==) :: ChartDims a -> ChartDims a -> Bool #

(/=) :: ChartDims a -> ChartDims a -> Bool #

Show a => Show (ChartDims a) Source # 
Instance details

Defined in Chart.Types

Generic (ChartDims a) Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep (ChartDims a) :: Type -> Type #

Methods

from :: ChartDims a -> Rep (ChartDims a) x #

to :: Rep (ChartDims a) x -> ChartDims a #

type Rep (ChartDims a) Source # 
Instance details

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)))))

newtype HudT m a Source #

Constructors

Hud 

Fields

Instances
Monad m => Semigroup (HudT m a) Source # 
Instance details

Defined in Chart.Types

Methods

(<>) :: HudT m a -> HudT m a -> HudT m a #

sconcat :: NonEmpty (HudT m a) -> HudT m a #

stimes :: Integral b => b -> HudT m a -> HudT m a #

Monad m => Monoid (HudT m a) Source # 
Instance details

Defined in Chart.Types

Methods

mempty :: HudT m a #

mappend :: HudT m a -> HudT m a -> HudT m a #

mconcat :: [HudT m a] -> HudT m 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.

Instances
Eq HudOptions Source # 
Instance details

Defined in Chart.Types

Show HudOptions Source # 
Instance details

Defined in Chart.Types

Generic HudOptions Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep HudOptions :: Type -> Type #

Semigroup HudOptions Source # 
Instance details

Defined in Chart.Types

Monoid HudOptions Source # 
Instance details

Defined in Chart.Types

type Rep HudOptions Source # 
Instance details

Defined in Chart.Types

data AxisOptions Source #

Constructors

AxisOptions 
Instances
Eq AxisOptions Source # 
Instance details

Defined in Chart.Types

Show AxisOptions Source # 
Instance details

Defined in Chart.Types

Generic AxisOptions Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep AxisOptions :: Type -> Type #

type Rep AxisOptions Source # 
Instance details

Defined in Chart.Types

data Place Source #

Placement of elements around (what is implicity but maybe shouldn't just be) a rectangular canvas

Instances
Eq Place Source # 
Instance details

Defined in Chart.Types

Methods

(==) :: Place -> Place -> Bool #

(/=) :: Place -> Place -> Bool #

Show Place Source # 
Instance details

Defined in Chart.Types

Methods

showsPrec :: Int -> Place -> ShowS #

show :: Place -> String #

showList :: [Place] -> ShowS #

Generic Place Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep Place :: Type -> Type #

Methods

from :: Place -> Rep Place x #

to :: Rep Place x -> Place #

type Rep Place Source # 
Instance details

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))))))

data Bar Source #

Constructors

Bar 

Fields

Instances
Eq Bar Source # 
Instance details

Defined in Chart.Types

Methods

(==) :: Bar -> Bar -> Bool #

(/=) :: Bar -> Bar -> Bool #

Show Bar Source # 
Instance details

Defined in Chart.Types

Methods

showsPrec :: Int -> Bar -> ShowS #

show :: Bar -> String #

showList :: [Bar] -> ShowS #

Generic Bar Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep Bar :: Type -> Type #

Methods

from :: Bar -> Rep Bar x #

to :: Rep Bar x -> Bar #

type Rep Bar Source # 
Instance details

Defined in Chart.Types

data Title Source #

Options for titles. Defaults to center aligned, and placed at Top of the hud

Constructors

Title 

Fields

Instances
Eq Title Source # 
Instance details

Defined in Chart.Types

Methods

(==) :: Title -> Title -> Bool #

(/=) :: Title -> Title -> Bool #

Show Title Source # 
Instance details

Defined in Chart.Types

Methods

showsPrec :: Int -> Title -> ShowS #

show :: Title -> String #

showList :: [Title] -> ShowS #

Generic Title Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep Title :: Type -> Type #

Methods

from :: Title -> Rep Title x #

to :: Rep Title x -> Title #

type Rep Title Source # 
Instance details

Defined in Chart.Types

data Tick Source #

Instances
Eq Tick Source # 
Instance details

Defined in Chart.Types

Methods

(==) :: Tick -> Tick -> Bool #

(/=) :: Tick -> Tick -> Bool #

Show Tick Source # 
Instance details

Defined in Chart.Types

Methods

showsPrec :: Int -> Tick -> ShowS #

show :: Tick -> String #

showList :: [Tick] -> ShowS #

Generic Tick Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep Tick :: Type -> Type #

Methods

from :: Tick -> Rep Tick x #

to :: Rep Tick x -> Tick #

type Rep Tick Source # 
Instance details

Defined in Chart.Types

data TickStyle 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
Eq TickStyle Source # 
Instance details

Defined in Chart.Types

Show TickStyle Source # 
Instance details

Defined in Chart.Types

Generic TickStyle Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep TickStyle :: Type -> Type #

type Rep TickStyle Source # 
Instance details

Defined in Chart.Types

data TickExtend Source #

Constructors

TickExtend 
NoTickExtend 
Instances
Eq TickExtend Source # 
Instance details

Defined in Chart.Types

Show TickExtend Source # 
Instance details

Defined in Chart.Types

Generic TickExtend Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep TickExtend :: Type -> Type #

type Rep TickExtend Source # 
Instance details

Defined in Chart.Types

type Rep TickExtend = D1 (MetaData "TickExtend" "Chart.Types" "chart-svg-0.0.3-7exTAOGVqFp4RtiGXqy9zP" False) (C1 (MetaCons "TickExtend" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NoTickExtend" PrefixI False) (U1 :: Type -> Type))

data Adjustments Source #

options for prettifying axis decorations

Instances
Eq Adjustments Source # 
Instance details

Defined in Chart.Types

Show Adjustments Source # 
Instance details

Defined in Chart.Types

Generic Adjustments Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep Adjustments :: Type -> Type #

type Rep Adjustments Source # 
Instance details

Defined in Chart.Types

data LegendOptions Source #

Legend options

Instances
Eq LegendOptions Source # 
Instance details

Defined in Chart.Types

Show LegendOptions Source # 
Instance details

Defined in Chart.Types

Generic LegendOptions Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep LegendOptions :: Type -> Type #

type Rep LegendOptions Source # 
Instance details

Defined in Chart.Types

data FormatN Source #

Instances
Eq FormatN Source # 
Instance details

Defined in Chart.Types

Methods

(==) :: FormatN -> FormatN -> Bool #

(/=) :: FormatN -> FormatN -> Bool #

Show FormatN Source # 
Instance details

Defined in Chart.Types

Generic FormatN Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep FormatN :: Type -> Type #

Methods

from :: FormatN -> Rep FormatN x #

to :: Rep FormatN x -> FormatN #

type Rep FormatN Source # 
Instance details

Defined in Chart.Types