hgeometry-ipe-0.11.0.0: Reading and Writing ipe7 files.

Safe HaskellNone
LanguageHaskell2010

Data.Geometry.Ipe.Path

Synopsis

Documentation

newtype Path r Source #

A path is a non-empty sequence of PathSegments.

Constructors

Path (LSeq 1 (PathSegment r)) 
Instances
Functor Path Source # 
Instance details

Defined in Data.Geometry.Ipe.Path

Methods

fmap :: (a -> b) -> Path a -> Path b #

(<$) :: a -> Path b -> Path a #

Foldable Path Source # 
Instance details

Defined in Data.Geometry.Ipe.Path

Methods

fold :: Monoid m => Path m -> m #

foldMap :: Monoid m => (a -> m) -> Path a -> m #

foldr :: (a -> b -> b) -> b -> Path a -> b #

foldr' :: (a -> b -> b) -> b -> Path a -> b #

foldl :: (b -> a -> b) -> b -> Path a -> b #

foldl' :: (b -> a -> b) -> b -> Path a -> b #

foldr1 :: (a -> a -> a) -> Path a -> a #

foldl1 :: (a -> a -> a) -> Path a -> a #

toList :: Path a -> [a] #

null :: Path a -> Bool #

length :: Path a -> Int #

elem :: Eq a => a -> Path a -> Bool #

maximum :: Ord a => Path a -> a #

minimum :: Ord a => Path a -> a #

sum :: Num a => Path a -> a #

product :: Num a => Path a -> a #

Traversable Path Source # 
Instance details

Defined in Data.Geometry.Ipe.Path

Methods

traverse :: Applicative f => (a -> f b) -> Path a -> f (Path b) #

sequenceA :: Applicative f => Path (f a) -> f (Path a) #

mapM :: Monad m => (a -> m b) -> Path a -> m (Path b) #

sequence :: Monad m => Path (m a) -> m (Path a) #

ToObject Path Source # 
Instance details

Defined in Data.Geometry.Ipe.Content

Eq r => Eq (Path r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Path

Methods

(==) :: Path r -> Path r -> Bool #

(/=) :: Path r -> Path r -> Bool #

Show r => Show (Path r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Path

Methods

showsPrec :: Int -> Path r -> ShowS #

show :: Path r -> String #

showList :: [Path r] -> ShowS #

Fractional r => IsTransformable (Path r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Path

Methods

transformBy :: Transformation (Dimension (Path r)) (NumType (Path r)) -> Path r -> Path r #

(Coordinate r, Eq r) => IpeRead (Path r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Reader

(Coordinate r, Eq r) => IpeReadText (Path r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Reader

IpeWriteText r => IpeWrite (Path r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Writer

Methods

ipeWrite :: Path r -> Maybe (Node Text Text) Source #

IpeWriteText r => IpeWriteText (Path r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Writer

type Dimension (Path r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Path

type Dimension (Path r) = 2
type NumType (Path r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Path

type NumType (Path r) = r

pathSegments :: forall r r. Iso (Path r) (Path r) (LSeq 1 (PathSegment r)) (LSeq 1 (PathSegment r)) Source #

data PathSegment r Source #

Paths

Paths consist of Path Segments. PathSegments come in the following forms:

Instances
Functor PathSegment Source # 
Instance details

Defined in Data.Geometry.Ipe.Path

Methods

fmap :: (a -> b) -> PathSegment a -> PathSegment b #

(<$) :: a -> PathSegment b -> PathSegment a #

Foldable PathSegment Source # 
Instance details

Defined in Data.Geometry.Ipe.Path

Methods

fold :: Monoid m => PathSegment m -> m #

foldMap :: Monoid m => (a -> m) -> PathSegment a -> m #

foldr :: (a -> b -> b) -> b -> PathSegment a -> b #

foldr' :: (a -> b -> b) -> b -> PathSegment a -> b #

foldl :: (b -> a -> b) -> b -> PathSegment a -> b #

foldl' :: (b -> a -> b) -> b -> PathSegment a -> b #

foldr1 :: (a -> a -> a) -> PathSegment a -> a #

foldl1 :: (a -> a -> a) -> PathSegment a -> a #

toList :: PathSegment a -> [a] #

null :: PathSegment a -> Bool #

length :: PathSegment a -> Int #

elem :: Eq a => a -> PathSegment a -> Bool #

maximum :: Ord a => PathSegment a -> a #

minimum :: Ord a => PathSegment a -> a #

sum :: Num a => PathSegment a -> a #

product :: Num a => PathSegment a -> a #

Traversable PathSegment Source # 
Instance details

Defined in Data.Geometry.Ipe.Path

Methods

traverse :: Applicative f => (a -> f b) -> PathSegment a -> f (PathSegment b) #

sequenceA :: Applicative f => PathSegment (f a) -> f (PathSegment a) #

mapM :: Monad m => (a -> m b) -> PathSegment a -> m (PathSegment b) #

sequence :: Monad m => PathSegment (m a) -> m (PathSegment a) #

Eq r => Eq (PathSegment r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Path

Show r => Show (PathSegment r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Path

Fractional r => IsTransformable (PathSegment r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Path

(Coordinate r, Eq r) => IpeReadText (NonEmpty (PathSegment r)) Source # 
Instance details

Defined in Data.Geometry.Ipe.Reader

IpeWriteText r => IpeWriteText (PathSegment r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Writer

type Dimension (PathSegment r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Path

type Dimension (PathSegment r) = 2
type NumType (PathSegment r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Path

type NumType (PathSegment r) = r

_ArcSegment :: forall r. Prism' (PathSegment r) () Source #

data Operation r Source #

type that represents a path in ipe.

Constructors

MoveTo (Point 2 r) 
LineTo (Point 2 r) 
CurveTo (Point 2 r) (Point 2 r) (Point 2 r) 
QCurveTo (Point 2 r) (Point 2 r) 
Ellipse (Matrix 3 3 r) 
ArcTo (Matrix 3 3 r) (Point 2 r) 
Spline [Point 2 r] 
ClosedSpline [Point 2 r] 
ClosePath 
Instances
Functor Operation Source # 
Instance details

Defined in Data.Geometry.Ipe.Path

Methods

fmap :: (a -> b) -> Operation a -> Operation b #

(<$) :: a -> Operation b -> Operation a #

Foldable Operation Source # 
Instance details

Defined in Data.Geometry.Ipe.Path

Methods

fold :: Monoid m => Operation m -> m #

foldMap :: Monoid m => (a -> m) -> Operation a -> m #

foldr :: (a -> b -> b) -> b -> Operation a -> b #

foldr' :: (a -> b -> b) -> b -> Operation a -> b #

foldl :: (b -> a -> b) -> b -> Operation a -> b #

foldl' :: (b -> a -> b) -> b -> Operation a -> b #

foldr1 :: (a -> a -> a) -> Operation a -> a #

foldl1 :: (a -> a -> a) -> Operation a -> a #

toList :: Operation a -> [a] #

null :: Operation a -> Bool #

length :: Operation a -> Int #

elem :: Eq a => a -> Operation a -> Bool #

maximum :: Ord a => Operation a -> a #

minimum :: Ord a => Operation a -> a #

sum :: Num a => Operation a -> a #

product :: Num a => Operation a -> a #

Traversable Operation Source # 
Instance details

Defined in Data.Geometry.Ipe.Path

Methods

traverse :: Applicative f => (a -> f b) -> Operation a -> f (Operation b) #

sequenceA :: Applicative f => Operation (f a) -> f (Operation a) #

mapM :: Monad m => (a -> m b) -> Operation a -> m (Operation b) #

sequence :: Monad m => Operation (m a) -> m (Operation a) #

Eq r => Eq (Operation r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Path

Methods

(==) :: Operation r -> Operation r -> Bool #

(/=) :: Operation r -> Operation r -> Bool #

Show r => Show (Operation r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Path

Coordinate r => IpeReadText [Operation r] Source # 
Instance details

Defined in Data.Geometry.Ipe.Reader

IpeWriteText r => IpeWriteText (Operation r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Writer

_MoveTo :: forall r. Prism' (Operation r) (Point 2 r) Source #

_LineTo :: forall r. Prism' (Operation r) (Point 2 r) Source #

_CurveTo :: forall r. Prism' (Operation r) (Point 2 r, Point 2 r, Point 2 r) Source #

_QCurveTo :: forall r. Prism' (Operation r) (Point 2 r, Point 2 r) Source #

_Ellipse :: forall r. Prism' (Operation r) (Matrix 3 3 r) Source #

_ArcTo :: forall r. Prism' (Operation r) (Matrix 3 3 r, Point 2 r) Source #

_Spline :: forall r. Prism' (Operation r) [Point 2 r] Source #

_ClosedSpline :: forall r. Prism' (Operation r) [Point 2 r] Source #

_ClosePath :: forall r. Prism' (Operation r) () Source #