chart-svg-0.3.1: Charting library targetting SVGs.
Safe HaskellNone
LanguageHaskell2010

Chart.Style

Description

Stylistic or syntactical options for chart elements.

Synopsis

RectStyle

data RectStyle Source #

Rectangle styling

>>> defaultRectStyle
RectStyle {borderSize = 1.0e-2, borderColor = Colour 0.02 0.29 0.48 1.00, color = Colour 0.02 0.73 0.80 0.10}

Constructors

RectStyle 

Instances

Instances details
Eq RectStyle Source # 
Instance details

Defined in Chart.Style

Show RectStyle Source # 
Instance details

Defined in Chart.Style

Generic RectStyle Source # 
Instance details

Defined in Chart.Style

Associated Types

type Rep RectStyle :: Type -> Type #

type Rep RectStyle Source # 
Instance details

Defined in Chart.Style

type Rep RectStyle = D1 ('MetaData "RectStyle" "Chart.Style" "chart-svg-0.3.1-ASe9AvMwv5fK1wYh9h4HnJ" 'False) (C1 ('MetaCons "RectStyle" 'PrefixI 'True) (S1 ('MetaSel ('Just "borderSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double) :*: (S1 ('MetaSel ('Just "borderColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Colour) :*: S1 ('MetaSel ('Just "color") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Colour))))

blob :: Colour -> RectStyle Source #

solid rectangle, no border

>>> blob black
RectStyle {borderSize = 0.0, borderColor = Colour 0.00 0.00 0.00 0.00, color = Colour 0.00 0.00 0.00 1.00}

clear :: RectStyle Source #

transparent rect

>>> clear
RectStyle {borderSize = 0.0, borderColor = Colour 0.00 0.00 0.00 0.00, color = Colour 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 = Colour 0.00 0.00 0.00 0.00, color = Colour 0.00 0.00 0.00 0.00}

TextStyle

data TextStyle Source #

Text styling

>>> defaultTextStyle
TextStyle {size = 0.12, color = Colour 0.05 0.05 0.05 1.00, anchor = AnchorMiddle, hsize = 0.45, vsize = 1.1, vshift = -0.25, rotation = Nothing, scalex = ScaleX, frame = Nothing}

Instances

Instances details
Eq TextStyle Source # 
Instance details

Defined in Chart.Style

Show TextStyle Source # 
Instance details

Defined in Chart.Style

Generic TextStyle Source # 
Instance details

Defined in Chart.Style

Associated Types

type Rep TextStyle :: Type -> Type #

type Rep TextStyle Source # 
Instance details

Defined in Chart.Style

defaultTextStyle :: TextStyle Source #

the offical text style

styleBoxText :: TextStyle -> Text -> Point Double -> Rect Double Source #

the extra area from text styling

data ScaleX Source #

Whether to scale text given X-axis scaling

Constructors

ScaleX 
NoScaleX 

Instances

Instances details
Eq ScaleX Source # 
Instance details

Defined in Chart.Style

Methods

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

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

Show ScaleX Source # 
Instance details

Defined in Chart.Style

Generic ScaleX Source # 
Instance details

Defined in Chart.Style

Associated Types

type Rep ScaleX :: Type -> Type #

Methods

from :: ScaleX -> Rep ScaleX x #

to :: Rep ScaleX x -> ScaleX #

type Rep ScaleX Source # 
Instance details

Defined in Chart.Style

type Rep ScaleX = D1 ('MetaData "ScaleX" "Chart.Style" "chart-svg-0.3.1-ASe9AvMwv5fK1wYh9h4HnJ" 'False) (C1 ('MetaCons "ScaleX" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoScaleX" 'PrefixI 'False) (U1 :: Type -> Type))

GlyphStyle

data GlyphStyle Source #

Glyph styling

>>> defaultGlyphStyle
GlyphStyle {size = 3.0e-2, color = Colour 0.02 0.73 0.80 0.20, borderColor = Colour 0.02 0.29 0.48 1.00, borderSize = 3.0e-3, shape = SquareGlyph, rotation = Nothing, translate = Nothing}

Constructors

GlyphStyle 

Fields

Instances

Instances details
Eq GlyphStyle Source # 
Instance details

Defined in Chart.Style

Show GlyphStyle Source # 
Instance details

Defined in Chart.Style

Generic GlyphStyle Source # 
Instance details

Defined in Chart.Style

Associated Types

type Rep GlyphStyle :: Type -> Type #

type Rep GlyphStyle Source # 
Instance details

Defined in Chart.Style

defaultGlyphStyle :: GlyphStyle Source #

the offical glyph style

styleBoxGlyph :: GlyphStyle -> Rect Double Source #

the extra area from glyph styling

gpalette1 :: Int -> GlyphShape Source #

Infinite list of glyph shapes

>>> gpalette1 0
CircleGlyph

data ScaleBorder Source #

Should glyph borders be scaled?

Constructors

ScaleBorder 
NoScaleBorder 

Instances

Instances details
Eq ScaleBorder Source # 
Instance details

Defined in Chart.Style

Show ScaleBorder Source # 
Instance details

Defined in Chart.Style

Generic ScaleBorder Source # 
Instance details

Defined in Chart.Style

Associated Types

type Rep ScaleBorder :: Type -> Type #

type Rep ScaleBorder Source # 
Instance details

Defined in Chart.Style

type Rep ScaleBorder = D1 ('MetaData "ScaleBorder" "Chart.Style" "chart-svg-0.3.1-ASe9AvMwv5fK1wYh9h4HnJ" 'False) (C1 ('MetaCons "ScaleBorder" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoScaleBorder" 'PrefixI 'False) (U1 :: Type -> Type))

data GlyphShape Source #

glyph shapes

Instances

Instances details
Eq GlyphShape Source # 
Instance details

Defined in Chart.Style

Show GlyphShape Source # 
Instance details

Defined in Chart.Style

Generic GlyphShape Source # 
Instance details

Defined in Chart.Style

Associated Types

type Rep GlyphShape :: Type -> Type #

type Rep GlyphShape Source # 
Instance details

Defined in Chart.Style

type Rep GlyphShape = D1 ('MetaData "GlyphShape" "Chart.Style" "chart-svg-0.3.1-ASe9AvMwv5fK1wYh9h4HnJ" '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 'DecidedStrict) (Rec0 Double)) :+: C1 ('MetaCons "RectSharpGlyph" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double)))) :+: ((C1 ('MetaCons "RectRoundedGlyph" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double))) :+: C1 ('MetaCons "TriangleGlyph" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Point Double)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Point Double)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Point Double))))) :+: (C1 ('MetaCons "VLineGlyph" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HLineGlyph" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PathGlyph" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ScaleBorder))))))

LineStyle

data LineStyle Source #

line style

>>> defaultLineStyle
LineStyle {size = 1.2e-2, color = Colour 0.05 0.05 0.05 1.00, linecap = Nothing, linejoin = Nothing, dasharray = Nothing, dashoffset = Nothing}

See also https://developer.mozilla.org/en-US/docs/Web/SVG/Attribute

Instances

Instances details
Eq LineStyle Source # 
Instance details

Defined in Chart.Style

Show LineStyle Source # 
Instance details

Defined in Chart.Style

Generic LineStyle Source # 
Instance details

Defined in Chart.Style

Associated Types

type Rep LineStyle :: Type -> Type #

type Rep LineStyle Source # 
Instance details

Defined in Chart.Style

defaultLineStyle :: LineStyle Source #

the official default line style

data LineCap Source #

line cap style

Instances

Instances details
Eq LineCap Source # 
Instance details

Defined in Chart.Style

Methods

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

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

Show LineCap Source # 
Instance details

Defined in Chart.Style

Generic LineCap Source # 
Instance details

Defined in Chart.Style

Associated Types

type Rep LineCap :: Type -> Type #

Methods

from :: LineCap -> Rep LineCap x #

to :: Rep LineCap x -> LineCap #

type Rep LineCap Source # 
Instance details

Defined in Chart.Style

type Rep LineCap = D1 ('MetaData "LineCap" "Chart.Style" "chart-svg-0.3.1-ASe9AvMwv5fK1wYh9h4HnJ" 'False) (C1 ('MetaCons "LineCapButt" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LineCapRound" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LineCapSquare" 'PrefixI 'False) (U1 :: Type -> Type)))

fromLineCap :: IsString s => LineCap -> s Source #

textifier

toLineCap :: (Eq s, IsString s) => s -> LineCap Source #

readifier

data LineJoin Source #

line cap style

Instances

Instances details
Eq LineJoin Source # 
Instance details

Defined in Chart.Style

Show LineJoin Source # 
Instance details

Defined in Chart.Style

Generic LineJoin Source # 
Instance details

Defined in Chart.Style

Associated Types

type Rep LineJoin :: Type -> Type #

Methods

from :: LineJoin -> Rep LineJoin x #

to :: Rep LineJoin x -> LineJoin #

type Rep LineJoin Source # 
Instance details

Defined in Chart.Style

type Rep LineJoin = D1 ('MetaData "LineJoin" "Chart.Style" "chart-svg-0.3.1-ASe9AvMwv5fK1wYh9h4HnJ" 'False) (C1 ('MetaCons "LineJoinMiter" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LineJoinBevel" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LineJoinRound" 'PrefixI 'False) (U1 :: Type -> Type)))

fromLineJoin :: IsString s => LineJoin -> s Source #

textifier

toLineJoin :: (Eq s, IsString s) => s -> LineJoin Source #

readifier

fromDashArray :: [Double] -> Text Source #

Convert a dash representation from a list to text

data Anchor Source #

position anchor

Instances

Instances details
Eq Anchor Source # 
Instance details

Defined in Chart.Style

Methods

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

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

Show Anchor Source # 
Instance details

Defined in Chart.Style

Generic Anchor Source # 
Instance details

Defined in Chart.Style

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.Style

type Rep Anchor = D1 ('MetaData "Anchor" "Chart.Style" "chart-svg-0.3.1-ASe9AvMwv5fK1wYh9h4HnJ" '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

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

from text

PathStyle

data PathStyle Source #

Path styling

>>> defaultPathStyle
PathStyle {borderSize = 1.0e-2, borderColor = Colour 0.02 0.29 0.48 1.00, color = Colour 0.66 0.07 0.55 1.00}

Constructors

PathStyle 

Instances

Instances details
Eq PathStyle Source # 
Instance details

Defined in Chart.Style

Show PathStyle Source # 
Instance details

Defined in Chart.Style

Generic PathStyle Source # 
Instance details

Defined in Chart.Style

Associated Types

type Rep PathStyle :: Type -> Type #

type Rep PathStyle Source # 
Instance details

Defined in Chart.Style

type Rep PathStyle = D1 ('MetaData "PathStyle" "Chart.Style" "chart-svg-0.3.1-ASe9AvMwv5fK1wYh9h4HnJ" 'False) (C1 ('MetaCons "PathStyle" 'PrefixI 'True) (S1 ('MetaSel ('Just "borderSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double) :*: (S1 ('MetaSel ('Just "borderColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Colour) :*: S1 ('MetaSel ('Just "color") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Colour))))