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

Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellNone
LanguageHaskell2010

Data.Geometry.Ipe.FromIpe

Contents

Description

Functions that help reading geometric values from ipe images.

Synopsis

Individual readers

_asPoint :: Prism' (IpeSymbol r) (Point 2 r) Source #

Extracts the point from a Symbol. When creating a symbol this creates a disk that supports a stroke color.

_asLineSegment :: Prism' (Path r) (LineSegment 2 () r) Source #

Try to convert a path into a line segment, fails if the path is not a line segment or a polyline with more than two points.

_asRectangle :: forall r. (Num r, Ord r) => Prism' (Path r) (Rectangle () r) Source #

Tries to convert a path into a rectangle.

_asTriangle :: Prism' (Path r) (Triangle 2 () r) Source #

Convert to a triangle

_asPolyLine :: Prism' (Path r) (PolyLine 2 () r) Source #

Convert to a polyline. Ignores all non-polyline parts

>>> testPath ^? _asPolyLine
Just (PolyLine {_points = LSeq (fromList [Point2 [0,0] :+ (),Point2 [10,10] :+ (),Point2 [200,100] :+ ()])})

_asSimplePolygon :: Prism' (Path r) (Polygon Simple () r) Source #

Convert to a simple polygon

_asMultiPolygon :: Prism' (Path r) (MultiPolygon () r) Source #

Convert to a multipolygon

Dealing with Attributes

_withAttrs :: Prism' (IpeObject r) (i r :+ IpeAttributes i r) -> Prism' (i r) g -> Prism' (IpeObject r) (g :+ IpeAttributes i r) Source #

Use the first prism to select the ipe object to depicle with, and the second how to select the geometry object from there on. Then we can select the geometry object, directly with its attributes here.

>>> testObject ^? _withAttrs _IpePath _asPolyLine
Just (PolyLine {_points = LSeq (fromList [Point2 [0,0] :+ (),Point2 [10,10] :+ (),Point2 [200,100] :+ ()])} :+ Attrs {NoAttr, NoAttr, NoAttr, NoAttr, Attr IpeColor (Named "red"), NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr})

Default readers

class HasDefaultFromIpe g where Source #

Associated Types

type DefaultFromIpe g :: * -> * Source #

Instances
HasDefaultFromIpe (Ellipse r) Source # 
Instance details

Defined in Data.Geometry.Ipe.FromIpe

Associated Types

type DefaultFromIpe (Ellipse r) :: Type -> Type Source #

HasDefaultFromIpe (SimplePolygon () r) Source # 
Instance details

Defined in Data.Geometry.Ipe.FromIpe

Associated Types

type DefaultFromIpe (SimplePolygon () r) :: Type -> Type Source #

HasDefaultFromIpe (MultiPolygon () r) Source # 
Instance details

Defined in Data.Geometry.Ipe.FromIpe

Associated Types

type DefaultFromIpe (MultiPolygon () r) :: Type -> Type Source #

(Floating r, Eq r) => HasDefaultFromIpe (Disk () r) Source # 
Instance details

Defined in Data.Geometry.Ipe.FromIpe

Associated Types

type DefaultFromIpe (Disk () r) :: Type -> Type Source #

Methods

defaultFromIpe :: r0 ~ NumType (Disk () r) => Prism' (IpeObject r0) (Disk () r :+ IpeAttributes (DefaultFromIpe (Disk () r)) r0) Source #

(Floating r, Eq r) => HasDefaultFromIpe (Circle () r) Source # 
Instance details

Defined in Data.Geometry.Ipe.FromIpe

Associated Types

type DefaultFromIpe (Circle () r) :: Type -> Type Source #

Methods

defaultFromIpe :: r0 ~ NumType (Circle () r) => Prism' (IpeObject r0) (Circle () r :+ IpeAttributes (DefaultFromIpe (Circle () r)) r0) Source #

HasDefaultFromIpe (Point 2 r) Source # 
Instance details

Defined in Data.Geometry.Ipe.FromIpe

Associated Types

type DefaultFromIpe (Point 2 r) :: Type -> Type Source #

HasDefaultFromIpe (PolyLine 2 () r) Source # 
Instance details

Defined in Data.Geometry.Ipe.FromIpe

Associated Types

type DefaultFromIpe (PolyLine 2 () r) :: Type -> Type Source #

Methods

defaultFromIpe :: r0 ~ NumType (PolyLine 2 () r) => Prism' (IpeObject r0) (PolyLine 2 () r :+ IpeAttributes (DefaultFromIpe (PolyLine 2 () r)) r0) Source #

HasDefaultFromIpe (LineSegment 2 () r) Source # 
Instance details

Defined in Data.Geometry.Ipe.FromIpe

Associated Types

type DefaultFromIpe (LineSegment 2 () r) :: Type -> Type Source #

Reading all elements of a particular type

readAll :: (HasDefaultFromIpe g, r ~ NumType g) => IpePage r -> [g :+ IpeAttributes (DefaultFromIpe g) r] Source #

Read all g's from some ipe page(s).

readAllFrom :: (HasDefaultFromIpe g, r ~ NumType g, Coordinate r, Eq r) => FilePath -> IO [g :+ IpeAttributes (DefaultFromIpe g) r] Source #

Convenience function from reading all g's from an ipe file. If there is an error reading or parsing the file the error is "thrown away".