| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Path
Contents
Description
SVG path manipulation
Synopsis
- data PathInfo a
- data ArcInfo a = ArcInfo {}
- data ArcPosition a = ArcPosition {}
- parsePath :: Text -> [PathCommand]
- toPathAbsolute :: (PathInfo Double, Point Double) -> Text
- toPathCommand :: (PathInfo Double, Point Double) -> PathCommand
- toPathAbsolutes :: [(PathInfo Double, Point Double)] -> Text
- toPathXYs :: [PathCommand] -> [(PathInfo Double, Point Double)]
- data ArcCentroid a = ArcCentroid {}
- arcCentroid :: (FromInteger a, Ord a, TrigField a, ExpField a) => ArcPosition a -> ArcCentroid a
- arcPosition :: (Ord a, Signed a, TrigField a) => ArcCentroid a -> ArcPosition a
- arcBox :: ArcPosition Double -> Rect Double
- arcDerivs :: Point Double -> Double -> (Double, Double)
- ellipse :: (Direction b a, Affinity b a, TrigField a) => b -> b -> a -> a -> b
- data QuadPosition a = QuadPosition {}
- data QuadPolar a = QuadPolar {}
- quadPosition :: (ExpField a, TrigField a) => QuadPolar a -> QuadPosition a
- quadPolar :: (Eq a, ExpField a, TrigField a) => QuadPosition a -> QuadPolar a
- quadBox :: QuadPosition Double -> Rect Double
- quadBezier :: (ExpField a, FromInteger a) => QuadPosition a -> a -> Point a
- quadDerivs :: QuadPosition Double -> [Double]
- data CubicPosition a = CubicPosition {
- cposStart :: Point a
- cposEnd :: Point a
- cposControl1 :: Point a
- cposControl2 :: Point a
- data CubicPolar a = CubicPolar {
- cpolStart :: Point a
- cpolEnd :: Point a
- cpolControl1 :: Polar a a
- cpolControl2 :: Polar a a
- cubicPosition :: (Eq a, ExpField a, TrigField a) => CubicPolar a -> CubicPosition a
- cubicPolar :: (Eq a, ExpField a, TrigField a) => CubicPosition a -> CubicPolar a
- cubicBox :: CubicPosition Double -> Rect Double
- cubicBezier :: (ExpField a, FromInteger a) => CubicPosition a -> a -> Point a
- cubicDerivs :: CubicPosition Double -> [Double]
- singletonCubic :: CubicPosition Double -> [(PathInfo Double, Point Double)]
- singletonQuad :: QuadPosition Double -> [(PathInfo Double, Point Double)]
- singletonArc :: ArcPosition Double -> [(PathInfo Double, Point Double)]
- singletonPie :: ArcPosition Double -> [(PathInfo Double, Point Double)]
- singletonPie' :: Point Double -> ArcPosition Double -> [(PathInfo Double, Point Double)]
- toSingletonArc :: [(PathInfo Double, Point Double)] -> Maybe (ArcPosition Double)
- pathBoxes :: [(PathInfo Double, Point Double)] -> Maybe (Rect Double)
- pathBox :: Point Double -> (PathInfo Double, Point Double) -> Rect Double
Path fundamental
Every element of an svg path can be thought of as exactly two points in space, with instructions of how to draw a curve between them. From this point of view, one which this library adopts, a path chart is thus very similar to a line chart. There's just a lot more information about the style of this line to deal with.
References:
To fit in with the requirements of the library design, specifically the separation of what a chart is into XY data Points from representation of these points, path instructions need to be decontructed into:
- define a single chart element as a line.
- split a single path element into the start and end points of the line, which become the
xysof aChart, and the rest of the information, which is calledPathInfoand incorporated into theChartannotation.
An arc path is variant to affine transformations of the xys points: angles are not presevred in the new reference frame.
Instances
| Eq a => Eq (PathInfo a) Source # | |
| Show a => Show (PathInfo a) Source # | |
| Generic (PathInfo a) Source # | |
| type Rep (PathInfo a) Source # | |
Defined in Data.Path type Rep (PathInfo a) = D1 ('MetaData "PathInfo" "Data.Path" "chart-svg-0.2.3-inplace" 'False) ((C1 ('MetaCons "StartI" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LineI" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CubicI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Point a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Point a))) :+: (C1 ('MetaCons "QuadI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Point a))) :+: C1 ('MetaCons "ArcI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (ArcInfo a)))))) | |
Information about an individual arc path.
Constructors
| ArcInfo | |
Instances
| Eq a => Eq (ArcInfo a) Source # | |
| Show a => Show (ArcInfo a) Source # | |
| Generic (ArcInfo a) Source # | |
| type Rep (ArcInfo a) Source # | |
Defined in Data.Path type Rep (ArcInfo a) = D1 ('MetaData "ArcInfo" "Data.Path" "chart-svg-0.2.3-inplace" 'False) (C1 ('MetaCons "ArcInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "radii") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Point a)) :*: S1 ('MetaSel ('Just "phi") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)) :*: (S1 ('MetaSel ('Just "large") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "clockwise") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool)))) | |
data ArcPosition a Source #
Specification of an Arc using positional referencing as per SVG standard.
Instances
parsePath :: Text -> [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[MoveTo OriginAbsolute [V2 (-1.0) 0.5],EllipticalArc OriginAbsolute [(0.5,0.5,0.0,True,True,V2 0.0 (-1.2320508075688774)),(1.0,1.0,0.0,False,False,V2 (-0.5) (-0.3660254037844387)),(1.0,1.0,0.0,False,False,V2 (-1.0) 0.5)],EndPath]
https://developer.mozilla.org/en-US/docs/Web/SVG/Attribute/d
convert from a path info, start point, end point triple to a path text clause.
Note that morally,
toPathsAbsolute . toInfos . parsePath == id
but the round trip destroys much information, including:
- path text spacing
- Z, which is replaced by a LineI instruction from the end point back to the original start of the path.
- Sequences of the same instruction type are uncompressed
- As the name suggests, relative paths are translated to absolute ones.
- implicit L's in multiple M instructions are separated.
In converting between chart-svg and SVG there are two changes in reference:
- arc rotation is expressed as positive degrees for a clockwise rotation in SVG, and counter-clockwise in radians for chart-svg
- A positive y-direction is down for SVG and up for chart-svg
Arguments
| :: (PathInfo Double, Point Double) | |
| -> PathCommand | path text |
Convert from PathInfo to PathCommand
toPathAbsolutes :: [(PathInfo Double, Point Double)] -> Text Source #
convert an (info, point) list to an svg d path text.
toPathXYs :: [PathCommand] -> [(PathInfo Double, Point Double)] Source #
Convert from a path command list to a PathA specification
data ArcCentroid a Source #
Arc specification based on centroidal interpretation.
See: https://www.w3.org/TR/SVG/implnote.html#ArcConversionEndpointToCenter
Constructors
| ArcCentroid | |
Instances
arcCentroid :: (FromInteger a, Ord a, TrigField a, ExpField a) => ArcPosition a -> ArcCentroid a Source #
convert from an ArcPosition spec to ArcCentroid spec.
See also this
>>>let p = ArcPosition (Point 0 0) (Point 1 0) (ArcInfo (Point 1 0.5) (pi/4) False True)>>>arcCentroid pArcCentroid {centroid = Point 0.20952624903444356 -0.48412291827592724, radius = Point 1.0 0.5, cphi = 0.7853981633974483, ang0 = 1.3753858999692936, angdiff = -1.823476581936975}
arcPosition :: (Ord a, Signed a, TrigField a) => ArcCentroid a -> ArcPosition a Source #
convert from an ArcCentroid to an ArcPosition specification.
Morally, > arcPosition . arcCentroid == id
Not isomorphic if:
- angle diff is pi and large is True
- radii are less than they should be and thus get scaled up.
arcBox :: ArcPosition Double -> Rect Double Source #
compute the bounding box for an arcBox
let p = ArcPosition (Point 0 0) (Point 1 0) (ArcInfo (Point 1 0.5) (pi/4) False True) arcBox p
Rect -8.326672684688674e-17 0.9999999999999998 -5.551115123125783e-17 0.30644649676616753
arcDerivs :: Point Double -> Double -> (Double, Double) Source #
potential arc turning points.
>>>arcDerivs (Point 1 0.5) (pi/4)(-0.4636476090008061,0.4636476090008062)
ellipse :: (Direction b a, Affinity b a, TrigField a) => b -> b -> a -> a -> b Source #
ellipse formulae
>>>ellipse zero (Point 1 2) (pi/6) piPoint -0.8660254037844388 -0.4999999999999997
Compare this "elegent" definition from stackexchange
\[\dfrac{((x-h)\cos(A)+(y-k)\sin(A))^2}{a^2}+\dfrac{((x-h) \sin(A)-(y-k) \cos(A))^2}{b^2}=1\]
with the haskell code:
c + (rotate phi |. (r * ray theta))
See also: wolfram
data QuadPosition a Source #
Quadratic bezier curve expressed in positional terms.
Constructors
| QuadPosition | |
Instances
Quadratic bezier curve with control point expressed in polar terms normalised to the start - end line.
Constructors
| QuadPolar | |
Instances
| Eq a => Eq (QuadPolar a) Source # | |
| Show a => Show (QuadPolar a) Source # | |
| Generic (QuadPolar a) Source # | |
| type Rep (QuadPolar a) Source # | |
Defined in Data.Path type Rep (QuadPolar a) = D1 ('MetaData "QuadPolar" "Data.Path" "chart-svg-0.2.3-inplace" 'False) (C1 ('MetaCons "QuadPolar" 'PrefixI 'True) (S1 ('MetaSel ('Just "qpolStart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Point a)) :*: (S1 ('MetaSel ('Just "qpolEnd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Point a)) :*: S1 ('MetaSel ('Just "qpolControl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Polar a a))))) | |
quadPosition :: (ExpField a, TrigField a) => QuadPolar a -> QuadPosition a Source #
Convert from a polar to a positional representation of a quadratic bezier.
quadPosition . quadPolar == id quadPolar . quadPosition == id
>>>quadPosition $ quadPolar (QuadPosition (Point 0 0) (Point 1 1) (Point 2 -1))QuadPosition {qposStart = Point 0.0 0.0, qposEnd = Point 1.0 1.0, qposControl = Point 2.0 -0.9999999999999998}
quadPolar :: (Eq a, ExpField a, TrigField a) => QuadPosition a -> QuadPolar a Source #
Convert from a positional to a polar representation of a cubic bezier.
>>>quadPolar (QuadPosition (Point 0 0) (Point 1 1) (Point 2 -1))QuadPolar {qpolStart = Point 0.0 0.0, qpolEnd = Point 1.0 1.0, qpolControl = Polar {magnitude = 2.1213203435596424, direction = -0.7853981633974483}}
quadBox :: QuadPosition Double -> Rect Double Source #
Bounding box for a QuadPosition
>>>quadBox (QuadPosition (Point 0 0) (Point 1 1) (Point 2 -1))Rect 0.0 1.3333333333333335 -0.33333333333333337 1.0
quadBezier :: (ExpField a, FromInteger a) => QuadPosition a -> a -> Point a Source #
The quadratic bezier equation
>>>quadBezier (QuadPosition (Point 0 0) (Point 1 1) (Point 2 -1)) 0.33333333Point 0.9999999933333332 -0.33333333333333326
quadDerivs :: QuadPosition Double -> [Double] Source #
QuadPosition turning points.
>>>quadDerivs (QuadPosition (Point 0 0) (Point 1 1) (Point 2 -1))[0.6666666666666666,0.3333333333333333]
data CubicPosition a Source #
cubic bezier curve
Note that the ordering is different to the svg standard.
Constructors
| CubicPosition | |
Fields
| |
Instances
data CubicPolar a Source #
A polar representation of a cubic bezier with control points expressed as polar and normalised to the start - end line.
Constructors
| CubicPolar | |
Fields
| |
Instances
| Eq a => Eq (CubicPolar a) Source # | |
Defined in Data.Path | |
| Show a => Show (CubicPolar a) Source # | |
Defined in Data.Path Methods showsPrec :: Int -> CubicPolar a -> ShowS # show :: CubicPolar a -> String # showList :: [CubicPolar a] -> ShowS # | |
| Generic (CubicPolar a) Source # | |
| type Rep (CubicPolar a) Source # | |
Defined in Data.Path type Rep (CubicPolar a) = D1 ('MetaData "CubicPolar" "Data.Path" "chart-svg-0.2.3-inplace" 'False) (C1 ('MetaCons "CubicPolar" 'PrefixI 'True) ((S1 ('MetaSel ('Just "cpolStart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Point a)) :*: S1 ('MetaSel ('Just "cpolEnd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Point a))) :*: (S1 ('MetaSel ('Just "cpolControl1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Polar a a)) :*: S1 ('MetaSel ('Just "cpolControl2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Polar a a))))) | |
cubicPosition :: (Eq a, ExpField a, TrigField a) => CubicPolar a -> CubicPosition a Source #
Convert from a polar to a positional representation of a cubic bezier.
cubicPosition . cubicPolar == id cubicPolar . cubicPosition == id
>>>cubicPosition $ cubicPolar (CubicPosition (Point 0 0) (Point 1 1) (Point 1 -1) (Point 0 2))CubicPosition {cposStart = Point 0.0 0.0, cposEnd = Point 1.0 1.0, cposControl1 = Point 1.0 -1.0, cposControl2 = Point 1.6653345369377348e-16 2.0}
cubicPolar :: (Eq a, ExpField a, TrigField a) => CubicPosition a -> CubicPolar a Source #
Convert from a positional to a polar representation of a cubic bezier.
cubicPosition . cubicPolar == id cubicPolar . cubicPosition == id
>>>cubicPolar (CubicPosition (Point 0 0) (Point 1 1) (Point 1 -1) (Point 0 2))CubicPolar {cpolStart = Point 0.0 0.0, cpolEnd = Point 1.0 1.0, cpolControl1 = Polar {magnitude = 1.1180339887498947, direction = -1.2490457723982544}, cpolControl2 = Polar {magnitude = 1.1180339887498947, direction = 1.8925468811915387}}
cubicBox :: CubicPosition Double -> Rect Double Source #
Bounding box for a CubicPosition
>>>cubicBox (CubicPosition (Point 0 0) (Point 1 1) (Point 1 -1) (Point 0 2))Rect 0.0 1.0 -0.20710678118654752 1.2071067811865475
cubicBezier :: (ExpField a, FromInteger a) => CubicPosition a -> a -> Point a Source #
The cubic bezier equation
>>>cubicBezier (CubicPosition (Point 0 0) (Point 1 1) (Point 1 -1) (Point 0 2)) 0.8535533905932737Point 0.6767766952966369 1.2071067811865475
cubicDerivs :: CubicPosition Double -> [Double] Source #
Turning point positions for a CubicPosition (0,1 or 2)
>>>cubicDerivs (CubicPosition (Point 0 0) (Point 1 1) (Point 1 -1) (Point 0 2))[0.8535533905932737,0.14644660940672624,0.5]
singletonCubic :: CubicPosition Double -> [(PathInfo Double, Point Double)] Source #
convert cubic position to path info.
singletonQuad :: QuadPosition Double -> [(PathInfo Double, Point Double)] Source #
convert quad position to path info.
singletonArc :: ArcPosition Double -> [(PathInfo Double, Point Double)] Source #
convert arc position to path info.
singletonPie :: ArcPosition Double -> [(PathInfo Double, Point Double)] Source #
convert arc position to a pie slice.
singletonPie' :: Point Double -> ArcPosition Double -> [(PathInfo Double, Point Double)] Source #
convert arc position to a pie slice, with a specific center.
toSingletonArc :: [(PathInfo Double, Point Double)] -> Maybe (ArcPosition Double) Source #
convert path info to an ArcPosition.