chart-svg-0.6.0.0: Charting library targetting SVGs.
Safe HaskellSafe-Inferred
LanguageGHC2021

Chart.Style

Description

Definition of the syntactical manifestation of chart elements.

Synopsis

Documentation

data Style Source #

Stylistic content of chart elements, involving how chart data is represented in the physical chart.

>>> defaultStyle
Style {size = 6.0e-2, borderSize = 1.0e-2, color = Colour 0.02 0.73 0.80 0.10, borderColor = Colour 0.02 0.29 0.48 1.00, scaleP = NoScaleP, anchor = AnchorMiddle, rotation = Nothing, translate = Nothing, escapeText = EscapeText, frame = Nothing, lineCap = Nothing, lineJoin = Nothing, dasharray = Nothing, dashoffset = Nothing, hsize = 0.6, vsize = 1.1, vshift = -0.25, glyphShape = SquareGlyph}

Constructors

Style 

Fields

Instances

Instances details
Generic Style Source # 
Instance details

Defined in Chart.Style

Associated Types

type Rep Style :: Type -> Type #

Methods

from :: Style -> Rep Style x #

to :: Rep Style x -> Style #

Show Style Source # 
Instance details

Defined in Chart.Style

Methods

showsPrec :: Int -> Style -> ShowS #

show :: Style -> String #

showList :: [Style] -> ShowS #

Eq Style Source # 
Instance details

Defined in Chart.Style

Methods

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

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

type Rep Style Source # 
Instance details

Defined in Chart.Style

type Rep Style = D1 ('MetaData "Style" "Chart.Style" "chart-svg-0.6.0.0-HjsGv1l8hv76XDZORokPY6" 'False) (C1 ('MetaCons "Style" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "size") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Just "borderSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)) :*: (S1 ('MetaSel ('Just "color") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Colour) :*: S1 ('MetaSel ('Just "borderColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Colour))) :*: ((S1 ('MetaSel ('Just "scaleP") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ScaleP) :*: S1 ('MetaSel ('Just "anchor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Anchor)) :*: (S1 ('MetaSel ('Just "rotation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Double)) :*: (S1 ('MetaSel ('Just "translate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Point Double))) :*: S1 ('MetaSel ('Just "escapeText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EscapeText))))) :*: (((S1 ('MetaSel ('Just "frame") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Style)) :*: S1 ('MetaSel ('Just "lineCap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LineCap))) :*: (S1 ('MetaSel ('Just "lineJoin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LineJoin)) :*: S1 ('MetaSel ('Just "dasharray") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Double])))) :*: ((S1 ('MetaSel ('Just "dashoffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Double)) :*: S1 ('MetaSel ('Just "hsize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)) :*: (S1 ('MetaSel ('Just "vsize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: (S1 ('MetaSel ('Just "vshift") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Just "glyphShape") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlyphShape)))))))

defaultStyle :: Style Source #

The official default style

>>> defaultStyle
Style {size = 6.0e-2, borderSize = 1.0e-2, color = Colour 0.02 0.73 0.80 0.10, borderColor = Colour 0.02 0.29 0.48 1.00, scaleP = NoScaleP, anchor = AnchorMiddle, rotation = Nothing, translate = Nothing, escapeText = EscapeText, frame = Nothing, lineCap = Nothing, lineJoin = Nothing, dasharray = Nothing, dashoffset = Nothing, hsize = 0.6, vsize = 1.1, vshift = -0.25, glyphShape = SquareGlyph}

scaleStyle :: Double -> Style -> Style Source #

Scale the size, borderSize and any translations of a Style.

RectStyle

defaultRectStyle :: Style Source #

The official style for rectangles.

>>> defaultRectStyle
Style {size = 6.0e-2, borderSize = 1.0e-2, color = Colour 0.02 0.73 0.80 0.10, borderColor = Colour 0.02 0.29 0.48 1.00, scaleP = NoScaleP, anchor = AnchorMiddle, rotation = Nothing, translate = Nothing, escapeText = EscapeText, frame = Nothing, lineCap = Nothing, lineJoin = Nothing, dasharray = Nothing, dashoffset = Nothing, hsize = 0.6, vsize = 1.1, vshift = -0.25, glyphShape = SquareGlyph}

blob :: Colour -> Style Source #

solid rectangle, no border

>>> blob black
Style {size = 6.0e-2, borderSize = 0.0, color = Colour 0.00 0.00 0.00 1.00, borderColor = Colour 0.00 0.00 0.00 0.00, scaleP = NoScaleP, anchor = AnchorMiddle, rotation = Nothing, translate = Nothing, escapeText = EscapeText, frame = Nothing, lineCap = Nothing, lineJoin = Nothing, dasharray = Nothing, dashoffset = Nothing, hsize = 0.6, vsize = 1.1, vshift = -0.25, glyphShape = SquareGlyph}

clear :: Style Source #

transparent rect

>>> clear
Style {size = 6.0e-2, borderSize = 0.0, color = Colour 0.00 0.00 0.00 0.00, borderColor = Colour 0.00 0.00 0.00 0.00, scaleP = NoScaleP, anchor = AnchorMiddle, rotation = Nothing, translate = Nothing, escapeText = EscapeText, frame = Nothing, lineCap = Nothing, lineJoin = Nothing, dasharray = Nothing, dashoffset = Nothing, hsize = 0.6, vsize = 1.1, vshift = -0.25, glyphShape = SquareGlyph}

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

transparent rectangle, with border

>>> border 0.01 transparent
Style {size = 6.0e-2, borderSize = 1.0e-2, color = Colour 0.00 0.00 0.00 0.00, borderColor = Colour 0.00 0.00 0.00 0.00, scaleP = NoScaleP, anchor = AnchorMiddle, rotation = Nothing, translate = Nothing, escapeText = EscapeText, frame = Nothing, lineCap = Nothing, lineJoin = Nothing, dasharray = Nothing, dashoffset = Nothing, hsize = 0.6, vsize = 1.1, vshift = -0.25, glyphShape = SquareGlyph}

TextStyle

defaultTextStyle :: Style Source #

The official style for text elements.

>>> defaultTextStyle
Style {size = 6.0e-2, borderSize = 1.0e-2, color = Colour 0.05 0.05 0.05 1.00, borderColor = Colour 0.02 0.29 0.48 1.00, scaleP = NoScaleP, anchor = AnchorMiddle, rotation = Nothing, translate = Nothing, escapeText = EscapeText, frame = Nothing, lineCap = Nothing, lineJoin = Nothing, dasharray = Nothing, dashoffset = Nothing, hsize = 0.6, vsize = 1.1, vshift = -0.25, glyphShape = SquareGlyph}

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

the extra area from text styling

data EscapeText Source #

Whether to escape the common XML escaped characters.

Constructors

EscapeText 
NoEscapeText 

Instances

Instances details
Generic EscapeText Source # 
Instance details

Defined in Chart.Style

Associated Types

type Rep EscapeText :: Type -> Type #

Show EscapeText Source # 
Instance details

Defined in Chart.Style

Eq EscapeText Source # 
Instance details

Defined in Chart.Style

type Rep EscapeText Source # 
Instance details

Defined in Chart.Style

type Rep EscapeText = D1 ('MetaData "EscapeText" "Chart.Style" "chart-svg-0.6.0.0-HjsGv1l8hv76XDZORokPY6" 'False) (C1 ('MetaCons "EscapeText" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoEscapeText" 'PrefixI 'False) (U1 :: Type -> Type))

GlyphStyle

defaultGlyphStyle :: Style Source #

The official style for glyphs.

>>> defaultGlyphStyle
Style {size = 3.0e-2, borderSize = 3.0e-3, color = Colour 0.02 0.73 0.80 0.20, borderColor = Colour 0.02 0.29 0.48 1.00, scaleP = NoScaleP, anchor = AnchorMiddle, rotation = Nothing, translate = Nothing, escapeText = EscapeText, frame = Nothing, lineCap = Nothing, lineJoin = Nothing, dasharray = Nothing, dashoffset = Nothing, hsize = 0.6, vsize = 1.1, vshift = -0.25, glyphShape = SquareGlyph}

styleBoxGlyph :: Style -> Rect Double Source #

the extra area from glyph styling

gpalette :: Int -> GlyphShape Source #

Infinite list of glyph shapes

>>> gpalette 0
CircleGlyph

data GlyphShape Source #

glyph shapes

Instances

Instances details
Generic GlyphShape Source # 
Instance details

Defined in Chart.Style

Associated Types

type Rep GlyphShape :: Type -> Type #

Show GlyphShape Source # 
Instance details

Defined in Chart.Style

Eq GlyphShape Source # 
Instance details

Defined in Chart.Style

type Rep GlyphShape Source # 
Instance details

Defined in Chart.Style

type Rep GlyphShape = D1 ('MetaData "GlyphShape" "Chart.Style" "chart-svg-0.6.0.0-HjsGv1l8hv76XDZORokPY6" '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) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HLineGlyph" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PathGlyph" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))))))

LineStyle

defaultLineStyle :: Style Source #

The official style for lines.

>>> defaultLineStyle
Style {size = 1.2e-2, borderSize = 1.0e-2, color = Colour 0.05 0.05 0.05 1.00, borderColor = Colour 0.02 0.29 0.48 1.00, scaleP = NoScaleP, anchor = AnchorMiddle, rotation = Nothing, translate = Nothing, escapeText = EscapeText, frame = Nothing, lineCap = Nothing, lineJoin = Nothing, dasharray = Nothing, dashoffset = Nothing, hsize = 0.6, vsize = 1.1, vshift = -0.25, glyphShape = SquareGlyph}

data LineCap Source #

line cap style

Instances

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

Show LineCap Source # 
Instance details

Defined in Chart.Style

Eq LineCap Source # 
Instance details

Defined in Chart.Style

Methods

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

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

type Rep LineCap Source # 
Instance details

Defined in Chart.Style

type Rep LineCap = D1 ('MetaData "LineCap" "Chart.Style" "chart-svg-0.6.0.0-HjsGv1l8hv76XDZORokPY6" '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 #

svg textifier

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

readifier

data LineJoin Source #

line cap style

Instances

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

Show LineJoin Source # 
Instance details

Defined in Chart.Style

Eq LineJoin Source # 
Instance details

Defined in Chart.Style

type Rep LineJoin Source # 
Instance details

Defined in Chart.Style

type Rep LineJoin = D1 ('MetaData "LineJoin" "Chart.Style" "chart-svg-0.6.0.0-HjsGv1l8hv76XDZORokPY6" '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 #

svg textifier

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

readifier

data Anchor Source #

position anchor

Instances

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

Show Anchor Source # 
Instance details

Defined in Chart.Style

Eq Anchor Source # 
Instance details

Defined in Chart.Style

Methods

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

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

type Rep Anchor Source # 
Instance details

Defined in Chart.Style

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

defaultPathStyle :: Style Source #

The official style for paths.

>>> defaultPathStyle
Style {size = 6.0e-2, borderSize = 1.0e-2, color = Colour 0.66 0.07 0.55 1.00, borderColor = Colour 0.02 0.29 0.48 1.00, scaleP = NoScaleP, anchor = AnchorMiddle, rotation = Nothing, translate = Nothing, escapeText = EscapeText, frame = Nothing, lineCap = Nothing, lineJoin = Nothing, dasharray = Nothing, dashoffset = Nothing, hsize = 0.6, vsize = 1.1, vshift = -0.25, glyphShape = SquareGlyph}

Style scaling

data ScaleP Source #

Scale Projection options

Constructors

NoScaleP

Do not scale under projection.

ScalePX

Scale based on the X axis ratio of a projection

ScalePY

Scale based on the Y axis ratio of a projection

ScalePMinDim

Scale based on minimum of (X axis, Y axis) ratio

ScalePArea

Scale based on the area ratio of a projection

Instances

Instances details
Generic ScaleP Source # 
Instance details

Defined in Chart.Style

Associated Types

type Rep ScaleP :: Type -> Type #

Methods

from :: ScaleP -> Rep ScaleP x #

to :: Rep ScaleP x -> ScaleP #

Show ScaleP Source # 
Instance details

Defined in Chart.Style

Eq ScaleP Source # 
Instance details

Defined in Chart.Style

Methods

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

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

type Rep ScaleP Source # 
Instance details

Defined in Chart.Style

type Rep ScaleP = D1 ('MetaData "ScaleP" "Chart.Style" "chart-svg-0.6.0.0-HjsGv1l8hv76XDZORokPY6" 'False) ((C1 ('MetaCons "NoScaleP" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ScalePX" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ScalePY" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ScalePMinDim" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ScalePArea" 'PrefixI 'False) (U1 :: Type -> Type))))

scaleRatio :: ScaleP -> Rect Double -> Rect Double -> Double Source #

given a ScaleP and two Rects, what is the scaling factor for a projection

Guards against scaling to zero or infinity