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

Data.Path

Description

SVG path manipulation

Synopsis

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:

SVG d

SVG path

data PathInfo a Source #

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 xys of a Chart, and the rest of the information, which is called PathInfo and incorporated into the Chart annotation.

An arc path is variant to affine transformations of the xys points: angles are not presevred in the new reference frame.

Constructors

StartI 
LineI 
CubicI (Point a) (Point a) 
QuadI (Point a) 
ArcI (ArcInfo a) 

Instances

Instances details
Eq a => Eq (PathInfo a) Source # 
Instance details

Defined in Data.Path

Methods

(==) :: PathInfo a -> PathInfo a -> Bool #

(/=) :: PathInfo a -> PathInfo a -> Bool #

Show a => Show (PathInfo a) Source # 
Instance details

Defined in Data.Path

Methods

showsPrec :: Int -> PathInfo a -> ShowS #

show :: PathInfo a -> String #

showList :: [PathInfo a] -> ShowS #

Generic (PathInfo a) Source # 
Instance details

Defined in Data.Path

Associated Types

type Rep (PathInfo a) :: Type -> Type #

Methods

from :: PathInfo a -> Rep (PathInfo a) x #

to :: Rep (PathInfo a) x -> PathInfo a #

type Rep (PathInfo a) Source # 
Instance details

Defined in Data.Path

data ArcInfo a Source #

Information about an individual arc path.

Constructors

ArcInfo 

Fields

  • radii :: Point a

    ellipse radii

  • phi :: a

    rotation of the ellipse. positive means counter-clockwise (which is different to SVG).

  • large :: Bool
     
  • clockwise :: Bool

    sweep means clockwise

Instances

Instances details
Eq a => Eq (ArcInfo a) Source # 
Instance details

Defined in Data.Path

Methods

(==) :: ArcInfo a -> ArcInfo a -> Bool #

(/=) :: ArcInfo a -> ArcInfo a -> Bool #

Show a => Show (ArcInfo a) Source # 
Instance details

Defined in Data.Path

Methods

showsPrec :: Int -> ArcInfo a -> ShowS #

show :: ArcInfo a -> String #

showList :: [ArcInfo a] -> ShowS #

Generic (ArcInfo a) Source # 
Instance details

Defined in Data.Path

Associated Types

type Rep (ArcInfo a) :: Type -> Type #

Methods

from :: ArcInfo a -> Rep (ArcInfo a) x #

to :: Rep (ArcInfo a) x -> ArcInfo a #

type Rep (ArcInfo a) Source # 
Instance details

Defined in Data.Path

type Rep (ArcInfo a) = D1 ('MetaData "ArcInfo" "Data.Path" "chart-svg-0.2.2-AJskDBGhW2w5nFQE5Ah360" '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.

Constructors

ArcPosition 

Fields

Instances

Instances details
Eq a => Eq (ArcPosition a) Source # 
Instance details

Defined in Data.Path

Show a => Show (ArcPosition a) Source # 
Instance details

Defined in Data.Path

Generic (ArcPosition a) Source # 
Instance details

Defined in Data.Path

Associated Types

type Rep (ArcPosition a) :: Type -> Type #

Methods

from :: ArcPosition a -> Rep (ArcPosition a) x #

to :: Rep (ArcPosition a) x -> ArcPosition a #

type Rep (ArcPosition a) Source # 
Instance details

Defined in Data.Path

type Rep (ArcPosition a) = D1 ('MetaData "ArcPosition" "Data.Path" "chart-svg-0.2.2-AJskDBGhW2w5nFQE5Ah360" 'False) (C1 ('MetaCons "ArcPosition" 'PrefixI 'True) (S1 ('MetaSel ('Just "posStart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Point a)) :*: (S1 ('MetaSel ('Just "posEnd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Point a)) :*: S1 ('MetaSel ('Just "posInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (ArcInfo a)))))

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

toPathAbsolute Source #

Arguments

:: (PathInfo Double, Point Double)

(info, start, end)

-> Text

path text

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

toPathCommand Source #

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 

Fields

  • centroid :: Point a

    ellipse center

  • radius :: Point a

    ellipse radii

  • cphi :: a

    ellipse rotation

  • ang0 :: a

    starting point angle to the x-axis

  • angdiff :: a

    difference between ending point angle and starting point angle

Instances

Instances details
Eq a => Eq (ArcCentroid a) Source # 
Instance details

Defined in Data.Path

Show a => Show (ArcCentroid a) Source # 
Instance details

Defined in Data.Path

Generic (ArcCentroid a) Source # 
Instance details

Defined in Data.Path

Associated Types

type Rep (ArcCentroid a) :: Type -> Type #

Methods

from :: ArcCentroid a -> Rep (ArcCentroid a) x #

to :: Rep (ArcCentroid a) x -> ArcCentroid a #

type Rep (ArcCentroid a) Source # 
Instance details

Defined in Data.Path

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 p
ArcCentroid {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) pi
Point -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 

Fields

Instances

Instances details
Eq a => Eq (QuadPosition a) Source # 
Instance details

Defined in Data.Path

Show a => Show (QuadPosition a) Source # 
Instance details

Defined in Data.Path

Generic (QuadPosition a) Source # 
Instance details

Defined in Data.Path

Associated Types

type Rep (QuadPosition a) :: Type -> Type #

Methods

from :: QuadPosition a -> Rep (QuadPosition a) x #

to :: Rep (QuadPosition a) x -> QuadPosition a #

type Rep (QuadPosition a) Source # 
Instance details

Defined in Data.Path

type Rep (QuadPosition a) = D1 ('MetaData "QuadPosition" "Data.Path" "chart-svg-0.2.2-AJskDBGhW2w5nFQE5Ah360" 'False) (C1 ('MetaCons "QuadPosition" 'PrefixI 'True) (S1 ('MetaSel ('Just "qposStart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Point a)) :*: (S1 ('MetaSel ('Just "qposEnd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Point a)) :*: S1 ('MetaSel ('Just "qposControl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Point a)))))

data QuadPolar a Source #

Quadratic bezier curve with control point expressed in polar terms normalised to the start - end line.

Constructors

QuadPolar 

Fields

Instances

Instances details
Eq a => Eq (QuadPolar a) Source # 
Instance details

Defined in Data.Path

Methods

(==) :: QuadPolar a -> QuadPolar a -> Bool #

(/=) :: QuadPolar a -> QuadPolar a -> Bool #

Show a => Show (QuadPolar a) Source # 
Instance details

Defined in Data.Path

Generic (QuadPolar a) Source # 
Instance details

Defined in Data.Path

Associated Types

type Rep (QuadPolar a) :: Type -> Type #

Methods

from :: QuadPolar a -> Rep (QuadPolar a) x #

to :: Rep (QuadPolar a) x -> QuadPolar a #

type Rep (QuadPolar a) Source # 
Instance details

Defined in Data.Path

type Rep (QuadPolar a) = D1 ('MetaData "QuadPolar" "Data.Path" "chart-svg-0.2.2-AJskDBGhW2w5nFQE5Ah360" '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 :: (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.33333333
Point 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

Instances details
Eq a => Eq (CubicPosition a) Source # 
Instance details

Defined in Data.Path

Show a => Show (CubicPosition a) Source # 
Instance details

Defined in Data.Path

Generic (CubicPosition a) Source # 
Instance details

Defined in Data.Path

Associated Types

type Rep (CubicPosition a) :: Type -> Type #

type Rep (CubicPosition a) Source # 
Instance details

Defined in Data.Path

type Rep (CubicPosition a) = D1 ('MetaData "CubicPosition" "Data.Path" "chart-svg-0.2.2-AJskDBGhW2w5nFQE5Ah360" 'False) (C1 ('MetaCons "CubicPosition" 'PrefixI 'True) ((S1 ('MetaSel ('Just "cposStart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Point a)) :*: S1 ('MetaSel ('Just "cposEnd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Point a))) :*: (S1 ('MetaSel ('Just "cposControl1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Point a)) :*: S1 ('MetaSel ('Just "cposControl2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Point a)))))

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

Instances details
Eq a => Eq (CubicPolar a) Source # 
Instance details

Defined in Data.Path

Methods

(==) :: CubicPolar a -> CubicPolar a -> Bool #

(/=) :: CubicPolar a -> CubicPolar a -> Bool #

Show a => Show (CubicPolar a) Source # 
Instance details

Defined in Data.Path

Generic (CubicPolar a) Source # 
Instance details

Defined in Data.Path

Associated Types

type Rep (CubicPolar a) :: Type -> Type #

Methods

from :: CubicPolar a -> Rep (CubicPolar a) x #

to :: Rep (CubicPolar a) x -> CubicPolar a #

type Rep (CubicPolar a) Source # 
Instance details

Defined in Data.Path

type Rep (CubicPolar a) = D1 ('MetaData "CubicPolar" "Data.Path" "chart-svg-0.2.2-AJskDBGhW2w5nFQE5Ah360" '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 :: (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 :: (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.8535533905932737
Point 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.

pathBoxes :: [(PathInfo Double, Point Double)] -> Maybe (Rect Double) Source #

Bounding box for a list of path XYs.

pathBox :: Point Double -> (PathInfo Double, Point Double) -> Rect Double Source #

Bounding box for a path info, start and end Points.