Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Definition of the syntactical manifestation of chart elements.
Synopsis
- data Style = Style {
- size :: Double
- borderSize :: Double
- color :: Colour
- borderColor :: Colour
- scaleP :: ScaleP
- anchor :: Anchor
- rotation :: Maybe Double
- translate :: Maybe (Point Double)
- escapeText :: EscapeText
- frame :: Maybe Style
- lineCap :: Maybe LineCap
- lineJoin :: Maybe LineJoin
- dasharray :: Maybe [Double]
- dashoffset :: Maybe Double
- hsize :: Double
- vsize :: Double
- vshift :: Double
- glyphShape :: GlyphShape
- defaultStyle :: Style
- scaleStyle :: Double -> Style -> Style
- defaultRectStyle :: Style
- blob :: Colour -> Style
- clear :: Style
- border :: Double -> Colour -> Style
- defaultTextStyle :: Style
- styleBoxText :: Style -> Text -> Point Double -> Rect Double
- data EscapeText
- defaultGlyphStyle :: Style
- styleBoxGlyph :: Style -> Rect Double
- gpalette :: Int -> GlyphShape
- data GlyphShape
- defaultLineStyle :: Style
- data LineCap
- fromLineCap :: IsString s => LineCap -> s
- toLineCap :: (Eq s, IsString s) => s -> LineCap
- data LineJoin
- fromLineJoin :: IsString s => LineJoin -> s
- toLineJoin :: (Eq s, IsString s) => s -> LineJoin
- data Anchor
- fromAnchor :: IsString s => Anchor -> s
- toAnchor :: (Eq s, IsString s) => s -> Anchor
- defaultPathStyle :: Style
- data ScaleP
- scaleRatio :: ScaleP -> Rect Double -> Rect Double -> Double
Documentation
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}
Style | |
|
Instances
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}
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.
Instances
Generic EscapeText Source # | |
Defined in Chart.Style type Rep EscapeText :: Type -> Type # from :: EscapeText -> Rep EscapeText x # to :: Rep EscapeText x -> EscapeText # | |
Show EscapeText Source # | |
Defined in Chart.Style showsPrec :: Int -> EscapeText -> ShowS # show :: EscapeText -> String # showList :: [EscapeText] -> ShowS # | |
Eq EscapeText Source # | |
Defined in Chart.Style (==) :: EscapeText -> EscapeText -> Bool # (/=) :: EscapeText -> EscapeText -> Bool # | |
type Rep EscapeText Source # | |
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}
gpalette :: Int -> GlyphShape Source #
Infinite list of glyph shapes
>>>
gpalette 0
CircleGlyph
data GlyphShape Source #
glyph shapes
CircleGlyph | |
SquareGlyph | |
EllipseGlyph Double | |
RectSharpGlyph Double | |
RectRoundedGlyph Double Double Double | |
TriangleGlyph (Point Double) (Point Double) (Point Double) | line width is determined by borderSize |
VLineGlyph | |
HLineGlyph | |
PathGlyph ByteString |
Instances
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}
line cap style
Instances
Generic LineCap Source # | |
Show LineCap Source # | |
Eq LineCap Source # | |
type Rep LineCap Source # | |
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
line cap style
Instances
Generic LineJoin Source # | |
Show LineJoin Source # | |
Eq LineJoin Source # | |
type Rep LineJoin Source # | |
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
position anchor
Instances
Generic Anchor Source # | |
Show Anchor Source # | |
Eq Anchor Source # | |
type Rep Anchor Source # | |
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
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
Scale Projection options
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
Generic ScaleP Source # | |
Show ScaleP Source # | |
Eq ScaleP Source # | |
type Rep ScaleP Source # | |
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)))) |