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

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

Data.Geometry.Ipe.IpeOut

Contents

Description

Functions that help drawing geometric values in ipe. An IpeOut is essenitally a function that converts a geometric type g into an IpeObject.

We also proivde a HasDefaultIpeOut typeclass that defines a default conversion function from a geometry type g to an ipe type.

Synopsis

Documentation

>>> :set -XOverloadedStrings
>>> :{
let myPolygon = fromPoints . map ext $ [origin, Point2 10 10, Point2 100 200]
:}

The IpeOut type and the default combinator to use it

type IpeOut g i r = g -> IpeObject' i r Source #

(!) :: IpeObject' i r -> IpeAttributes i r -> IpeObject' i r Source #

Add attributes to an IpeObject'

iO :: ToObject i => IpeObject' i r -> IpeObject r Source #

Render an ipe object

>>> :{
  iO $ defIO myPolygon ! attr SFill (IpeColor "blue")
                       ! attr SLayer "alpha"
                       ! attr SLayer "beta"
:}
IpePath (Path {_pathSegments = LSeq (fromList [PolygonPath SimplePolygon CSeq [Point2 [0,0] :+ (),Point2 [10,10] :+ (),Point2 [100,200] :+ ()]])} :+ Attrs {Attr LayerName {_layerName = "beta"}, NoAttr, NoAttr, NoAttr, NoAttr, Attr IpeColor (Named "blue"), NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr})
>>> :{
  iO $ ipeGroup [ iO $ ipePolygon myPolygon ! attr SFill (IpeColor "red")
                ] ! attr SLayer "alpha"
:}
IpeGroup (Group [IpePath (Path {_pathSegments = LSeq (fromList [PolygonPath SimplePolygon CSeq [Point2 [0,0] :+ (),Point2 [10,10] :+ (),Point2 [100,200] :+ ()]])} :+ Attrs {NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, Attr IpeColor (Named "red"), NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr})] :+ Attrs {Attr LayerName {_layerName = "alpha"}, NoAttr, NoAttr, NoAttr, NoAttr})

iO'' :: (HasDefaultIpeOut g, NumType g ~ r, DefaultIpeOut g ~ i, ToObject i) => g -> IpeAttributes i r -> IpeObject r Source #

Render to an ipe object using the defIO IpeOut

>>> :{
  iO'' myPolygon $  attr SFill (IpeColor "red")
                 <> attr SLayer "alpha"
                 <> attr SLayer "beta"
:}
IpePath (Path {_pathSegments = LSeq (fromList [PolygonPath SimplePolygon CSeq [Point2 [0,0] :+ (),Point2 [10,10] :+ (),Point2 [100,200] :+ ()]])} :+ Attrs {Attr LayerName {_layerName = "beta"}, NoAttr, NoAttr, NoAttr, NoAttr, Attr IpeColor (Named "red"), NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr})
>>> iO'' [ myPolygon , myPolygon ] $ attr SLayer "alpha"
IpeGroup (Group [IpePath (Path {_pathSegments = LSeq (fromList [PolygonPath SimplePolygon CSeq [Point2 [0,0] :+ (),Point2 [10,10] :+ (),Point2 [100,200] :+ ()]])} :+ Attrs {NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr}),IpePath (Path {_pathSegments = LSeq (fromList [PolygonPath SimplePolygon CSeq [Point2 [0,0] :+ (),Point2 [10,10] :+ (),Point2 [100,200] :+ ()]])} :+ Attrs {NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr})] :+ Attrs {Attr LayerName {_layerName = "alpha"}, NoAttr, NoAttr, NoAttr, NoAttr})

iO' :: HasDefaultIpeOut g => g -> IpeObject (NumType g) Source #

generate an ipe object without any specific attributes

Default Conversions

class ToObject (DefaultIpeOut g) => HasDefaultIpeOut g where Source #

Class that specifies a default conversion from a geometry type g into an ipe object.

Associated Types

type DefaultIpeOut g :: * -> * Source #

Methods

defIO :: IpeOut g (DefaultIpeOut g) (NumType g) Source #

Instances
HasDefaultIpeOut a => HasDefaultIpeOut [a] Source # 
Instance details

Defined in Data.Geometry.Ipe.IpeOut

Associated Types

type DefaultIpeOut [a] :: Type -> Type Source #

Methods

defIO :: IpeOut [a] (DefaultIpeOut [a]) (NumType [a]) Source #

(HasDefaultIpeOut g, a ~ IpeAttributes (DefaultIpeOut g) (NumType g)) => HasDefaultIpeOut (g :+ a) Source # 
Instance details

Defined in Data.Geometry.Ipe.IpeOut

Associated Types

type DefaultIpeOut (g :+ a) :: Type -> Type Source #

Methods

defIO :: IpeOut (g :+ a) (DefaultIpeOut (g :+ a)) (NumType (g :+ a)) Source #

HasDefaultIpeOut (Point 2 r) Source # 
Instance details

Defined in Data.Geometry.Ipe.IpeOut

Associated Types

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

Methods

defIO :: IpeOut (Point 2 r) (DefaultIpeOut (Point 2 r)) (NumType (Point 2 r)) Source #

HasDefaultIpeOut (SomePolygon p r) Source # 
Instance details

Defined in Data.Geometry.Ipe.IpeOut

Associated Types

type DefaultIpeOut (SomePolygon p r) :: Type -> Type Source #

Methods

defIO :: IpeOut (SomePolygon p r) (DefaultIpeOut (SomePolygon p r)) (NumType (SomePolygon p r)) Source #

(Fractional r, Ord r) => HasDefaultIpeOut (Line 2 r) Source # 
Instance details

Defined in Data.Geometry.Ipe.IpeOut

Associated Types

type DefaultIpeOut (Line 2 r) :: Type -> Type Source #

Methods

defIO :: IpeOut (Line 2 r) (DefaultIpeOut (Line 2 r)) (NumType (Line 2 r)) Source #

Floating r => HasDefaultIpeOut (Disk p r) Source # 
Instance details

Defined in Data.Geometry.Ipe.IpeOut

Associated Types

type DefaultIpeOut (Disk p r) :: Type -> Type Source #

Methods

defIO :: IpeOut (Disk p r) (DefaultIpeOut (Disk p r)) (NumType (Disk p r)) Source #

HasDefaultIpeOut (ConvexPolygon p r) Source # 
Instance details

Defined in Data.Geometry.Ipe.IpeOut

Associated Types

type DefaultIpeOut (ConvexPolygon p r) :: Type -> Type Source #

Methods

defIO :: IpeOut (ConvexPolygon p r) (DefaultIpeOut (ConvexPolygon p r)) (NumType (ConvexPolygon p r)) Source #

HasDefaultIpeOut (LineSegment 2 p r) Source # 
Instance details

Defined in Data.Geometry.Ipe.IpeOut

Associated Types

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

Methods

defIO :: IpeOut (LineSegment 2 p r) (DefaultIpeOut (LineSegment 2 p r)) (NumType (LineSegment 2 p r)) Source #

HasDefaultIpeOut (PolyLine 2 p r) Source # 
Instance details

Defined in Data.Geometry.Ipe.IpeOut

Associated Types

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

Methods

defIO :: IpeOut (PolyLine 2 p r) (DefaultIpeOut (PolyLine 2 p r)) (NumType (PolyLine 2 p r)) Source #

HasDefaultIpeOut (Polygon t p r) Source # 
Instance details

Defined in Data.Geometry.Ipe.IpeOut

Associated Types

type DefaultIpeOut (Polygon t p r) :: Type -> Type Source #

Methods

defIO :: IpeOut (Polygon t p r) (DefaultIpeOut (Polygon t p r)) (NumType (Polygon t p r)) Source #

Point Converters

ipeMark :: Text -> IpeOut (Point 2 r) IpeSymbol r Source #

Path Converters

ipeLineSegment :: IpeOut (LineSegment 2 p r) Path r Source #

ipePolyLine :: IpeOut (PolyLine 2 p r) Path r Source #

ipeDisk :: Floating r => IpeOut (Disk p r) Path r Source #

ipeCircle :: Floating r => IpeOut (Circle p r) Path r Source #

path :: PathSegment r -> Path r Source #

Helper to construct a path from a singleton item

pathSegment :: LineSegment 2 p r -> PathSegment r Source #

ipePolygon :: IpeOut (Polygon t p r) Path r Source #

Draw a polygon

Group Converters