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

Data.Path.Parser

Contents

Description

Conversions to and from an SVG path to a PathData

Synopsis

Parsing

parsePath :: ByteString -> Maybe [PathCommand] Source #

Parse a raw path string.

>>> let outerseg1 = "M-1.0,0.5 A0.5 0.5 0.0 1 1 0.0,-1.2320508075688774 1.0 1.0 0.0 0 0 -0.5,-0.3660254037844387 1.0 1.0 0.0 0 0 -1.0,0.5 Z"
>>> parsePath outerseg1
Just [MoveTo OriginAbsolute [Point (-1.0) 0.5],EllipticalArc OriginAbsolute [(0.5,0.5,0.0,True,True,Point 0.0 (-1.2320508075688774)),(1.0,1.0,0.0,False,False,Point (-0.5) (-0.3660254037844387)),(1.0,1.0,0.0,False,False,Point (-1.0) 0.5)],EndPath]

pathParser :: Parser e [PathCommand] Source #

Parser for PathCommands

manyComma :: Parser e a -> Parser e [a] Source #

Items separated by a comma and one or more whitespace tokens either side.

svgToPathData :: ByteString -> [PathData Double] Source #

Convert from an SVG d attribute text snippet to a [PathData Double]

pathDataToSvg :: [PathData Double] -> ByteString Source #

Convert from [PathData Double] to an SVG d path text snippet.

data PathCommand Source #

Path command definition (ripped from reanimate-svg).

Constructors

MoveTo !Origin ![Point Double]

M or m command

LineTo !Origin ![Point Double]

Line to, L or l Svg path command.

HorizontalTo !Origin ![Double]

Equivalent to the H or h svg path command.

VerticalTo !Origin ![Double]

Equivalent to the V or v svg path command.

CurveTo !Origin ![(Point Double, Point Double, Point Double)]

Cubic bezier, C or c command

SmoothCurveTo !Origin ![(Point Double, Point Double)]

Smooth cubic bezier, equivalent to S or s command

QuadraticBezier !Origin ![(Point Double, Point Double)]

Quadratic bezier, Q or q command

SmoothQuadraticBezierCurveTo !Origin ![Point Double]

Quadratic bezier, T or t command

EllipticalArc !Origin ![(Double, Double, Double, Bool, Bool, Point Double)]

Elliptical arc, A or a command.

EndPath

Close the path, Z or z svg path command.

Instances

Instances details
Generic PathCommand Source # 
Instance details

Defined in Data.Path.Parser

Associated Types

type Rep PathCommand :: Type -> Type #

Show PathCommand Source # 
Instance details

Defined in Data.Path.Parser

Eq PathCommand Source # 
Instance details

Defined in Data.Path.Parser

type Rep PathCommand Source # 
Instance details

Defined in Data.Path.Parser

type Rep PathCommand = D1 ('MetaData "PathCommand" "Data.Path.Parser" "chart-svg-0.6.0.0-HjsGv1l8hv76XDZORokPY6" 'False) (((C1 ('MetaCons "MoveTo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Origin) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Point Double])) :+: C1 ('MetaCons "LineTo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Origin) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Point Double]))) :+: (C1 ('MetaCons "HorizontalTo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Origin) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Double])) :+: (C1 ('MetaCons "VerticalTo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Origin) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Double])) :+: C1 ('MetaCons "CurveTo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Origin) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Point Double, Point Double, Point Double)]))))) :+: ((C1 ('MetaCons "SmoothCurveTo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Origin) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Point Double, Point Double)])) :+: C1 ('MetaCons "QuadraticBezier" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Origin) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Point Double, Point Double)]))) :+: (C1 ('MetaCons "SmoothQuadraticBezierCurveTo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Origin) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Point Double])) :+: (C1 ('MetaCons "EllipticalArc" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Origin) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Double, Double, Double, Bool, Bool, Point Double)])) :+: C1 ('MetaCons "EndPath" 'PrefixI 'False) (U1 :: Type -> Type)))))

data Origin Source #

Tell if a path command is absolute (in the current user coordiante) or relative to the previous point.

Constructors

OriginAbsolute

Next point in absolute coordinate

OriginRelative

Next point relative to the previous

Instances

Instances details
Generic Origin Source # 
Instance details

Defined in Data.Path.Parser

Associated Types

type Rep Origin :: Type -> Type #

Methods

from :: Origin -> Rep Origin x #

to :: Rep Origin x -> Origin #

Show Origin Source # 
Instance details

Defined in Data.Path.Parser

Eq Origin Source # 
Instance details

Defined in Data.Path.Parser

Methods

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

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

type Rep Origin Source # 
Instance details

Defined in Data.Path.Parser

type Rep Origin = D1 ('MetaData "Origin" "Data.Path.Parser" "chart-svg-0.6.0.0-HjsGv1l8hv76XDZORokPY6" 'False) (C1 ('MetaCons "OriginAbsolute" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OriginRelative" 'PrefixI 'False) (U1 :: Type -> Type))

toPathDatas :: [PathCommand] -> [PathData Double] Source #

Convert from a path command list to a PathA specification