hgeometry-ipe-0.13: Reading and Writing ipe7 files.
Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellNone
LanguageHaskell2010

Ipe.IpeOut

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 #

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

Give the option to draw zero, one or more things, i.e. by choosing f ~ Maybe or f ~ []

(!) :: 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 #

Instances

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

Defined in Ipe.IpeOut

Associated Types

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

Methods

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

HasDefaultIpeOut (Ellipse r) Source # 
Instance details

Defined in Ipe.IpeOut

Associated Types

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

HasDefaultIpeOut (ConvexPolygon p r) Source # 
Instance details

Defined in Ipe.IpeOut

Associated Types

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

HasDefaultIpeOut (SomePolygon p r) Source # 
Instance details

Defined in Ipe.IpeOut

Associated Types

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

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

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

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

Defined in Ipe.IpeOut

Associated Types

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

Methods

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

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

Defined in Ipe.IpeOut

Associated Types

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

Num r => HasDefaultIpeOut (Rectangle p r) Source # 
Instance details

Defined in Ipe.IpeOut

Associated Types

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

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

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

HasDefaultIpeOut (Point 2 r) Source # 
Instance details

Defined in 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 g, a ~ IpeAttributes (DefaultIpeOut g) (NumType g)) => HasDefaultIpeOut (g :+ a) Source # 
Instance details

Defined in Ipe.IpeOut

Associated Types

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

Methods

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

HasDefaultIpeOut (Polygon t p r) Source # 
Instance details

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

HasDefaultIpeOut (PolyLine 2 p r) Source # 
Instance details

Defined in 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 (LineSegment 2 p r) Source # 
Instance details

Defined in Ipe.IpeOut

Associated Types

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

Point Converters

Path Converters

defaultBox :: Num r => Rectangle () r Source #

Size of the default bounding box used to clip lines and half-lines in the default IpeOuts.

ipeLine :: (Ord r, Fractional r) => IpeOut (Line 2 r) Path r Source #

Renders a line as a Path. The line is clipped to the defaultBox

ipeLineIn :: forall p r. (Ord r, Fractional r) => Rectangle p r -> IpeOut (Line 2 r) Path r Source #

Renders the line in the given box.

pre: the intersection of the box with the line is non-empty

ipeHalfLine :: (Ord r, Fractional r) => IpeOut (HalfLine 2 r) Path r Source #

Renders an Halfine.

pre: the intersection of the box with the line is non-empty

ipeHalfLineIn :: forall p r. (Ord r, Fractional r) => Rectangle p r -> IpeOut (HalfLine 2 r) Path r Source #

Renders the HalfLine in the given box.

pre: the intersection of the box with the line is non-empty

path :: PathSegment r -> Path r Source #

Helper to construct a path from a singleton item

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

Draw a polygon

ipeRectangle :: Num r => IpeOut (Rectangle p r) Path r Source #

Draw a Rectangle

Group Converters

Text Converters

ipeLabel :: IpeOut (Text :+ Point 2 r) TextLabel r Source #

Creates an text label

labelled Source #

Arguments

:: (Show lbl, NumType g ~ r, ToObject i) 
=> (g -> Point 2 r)

where to place the label

-> IpeOut g i r

how to draw the geometric object

-> IpeOut (g :+ lbl) Group r 

Annotate an IpeOut with a label