chart-svg-0.4.0: Charting library targetting SVGs.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Path

Description

SVG path manipulation

Synopsis

Svg Paths

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 to deal with.

References:

SVG d

SVG path

data PathData a Source #

Representation of a single SVG path data point

Constructors

StartP (Point a)

Starting position

LineP (Point a)

line (from previous position)

CubicP (Point a) (Point a) (Point a)

cubic bezier curve

QuadP (Point a) (Point a)

quad bezier curve

ArcP (ArcInfo a) (Point a) 

Instances

Instances details
Generic (PathData a) Source # 
Instance details

Defined in Data.Path

Associated Types

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

Methods

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

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

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

Defined in Data.Path

Methods

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

show :: PathData a -> String #

showList :: [PathData a] -> ShowS #

Eq a => Eq (PathData a) Source # 
Instance details

Defined in Data.Path

Methods

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

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

type Rep (PathData a) Source # 
Instance details

Defined in Data.Path

pointPath :: PathData a -> Point a Source #

View the Point part of a PathData

movePath :: Additive a => Point a -> PathData a -> PathData a Source #

Move the Point part of a PathData

scalePath :: Multiplicative a => a -> PathData a -> PathData a Source #

Multiplicatively scale a PathData

projectPaths :: Rect Double -> Rect Double -> [PathData Double] -> [PathData Double] Source #

Project a list of connected PathDatas from one Rect (XY plave) to a new one.

pathBoxes :: [PathData Double] -> Maybe (Rect Double) Source #

Bounding box for a list of path XYs.

pathBox :: Point Double -> PathData Double -> Rect Double Source #

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

Path maths

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

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 #

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

Defined in Data.Path

Methods

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

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

type Rep (ArcInfo a) Source # 
Instance details

Defined in Data.Path

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

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

Defined in Data.Path

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

Defined in Data.Path

type Rep (ArcPosition a) Source # 
Instance details

Defined in Data.Path

type Rep (ArcPosition a) = D1 ('MetaData "ArcPosition" "Data.Path" "chart-svg-0.4.0-IvsDYjPAAoJCAgDXwgibUh" '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)))))

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

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

Defined in Data.Path

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

Defined in Data.Path

type Rep (ArcCentroid a) Source # 
Instance details

Defined in Data.Path

arcCentroid :: (Ord a, FromInteger 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)
>>> import Data.FormatN
>>> fmap (fixed (Just 3)) (arcBox p)
Rect "-0.000" "1.000" "-0.000" "0.306"

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

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

Defined in Data.Path

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

Defined in Data.Path

type Rep (QuadPosition a) Source # 
Instance details

Defined in Data.Path

type Rep (QuadPosition a) = D1 ('MetaData "QuadPosition" "Data.Path" "chart-svg-0.4.0-IvsDYjPAAoJCAgDXwgibUh" '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
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 #

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

Defined in Data.Path

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

Defined in Data.Path

Methods

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

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

type Rep (QuadPolar a) Source # 
Instance details

Defined in Data.Path

type Rep (QuadPolar a) = D1 ('MetaData "QuadPolar" "Data.Path" "chart-svg-0.4.0-IvsDYjPAAoJCAgDXwgibUh" '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 :: 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, TrigField a, ExpField 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 :: (FromInteger a, ExpField 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
Generic (CubicPosition a) Source # 
Instance details

Defined in Data.Path

Associated Types

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

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

Defined in Data.Path

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

Defined in Data.Path

type Rep (CubicPosition a) Source # 
Instance details

Defined in Data.Path

type Rep (CubicPosition a) = D1 ('MetaData "CubicPosition" "Data.Path" "chart-svg-0.4.0-IvsDYjPAAoJCAgDXwgibUh" '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
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 #

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

Defined in Data.Path

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

Defined in Data.Path

Methods

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

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

type Rep (CubicPolar a) Source # 
Instance details

Defined in Data.Path

type Rep (CubicPolar a) = D1 ('MetaData "CubicPolar" "Data.Path" "chart-svg-0.4.0-IvsDYjPAAoJCAgDXwgibUh" '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, TrigField a, ExpField 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 :: (FromInteger a, TrigField 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 -> [PathData Double] Source #

Convert cubic position to path data.

singletonQuad :: QuadPosition Double -> [PathData Double] Source #

Convert quad position to path data.

singletonArc :: ArcPosition Double -> [PathData Double] Source #

Convert arc position to path data.

singletonPie :: Point Double -> ArcPosition Double -> [PathData Double] Source #

Convert arc position to a pie slice, with a specific center.