hgeometry-0.6.0.0: Geometric Algorithms, Data structures, and Data types.

Safe HaskellNone
LanguageHaskell2010

Data.Geometry.Ipe.Types

Contents

Synopsis

Documentation

data Image r Source #

Image Objects

Constructors

Image 

Fields

Instances

ToObject Image Source # 
Eq r => Eq (Image r) Source # 

Methods

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

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

Ord r => Ord (Image r) Source # 

Methods

compare :: Image r -> Image r -> Ordering #

(<) :: Image r -> Image r -> Bool #

(<=) :: Image r -> Image r -> Bool #

(>) :: Image r -> Image r -> Bool #

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

max :: Image r -> Image r -> Image r #

min :: Image r -> Image r -> Image r #

Show r => Show (Image r) Source # 

Methods

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

show :: Image r -> String #

showList :: [Image r] -> ShowS #

Num r => IsTransformable (Image r) Source # 
Coordinate r => IpeRead (Image r) Source # 
IpeWriteText r => IpeWrite (Image r) Source # 
type NumType (Image r) Source # 
type NumType (Image r) = r
type Dimension (Image r) Source # 
type Dimension (Image r) = 2

rect :: forall r r. Lens (Image r) (Image r) (Rectangle () r) (Rectangle () r) Source #

imageData :: forall r. Lens' (Image r) () Source #

data IpeSymbol r Source #

Ipe Symbols, i.e. Points

A symbol (point) in ipe

Constructors

Symbol 

Fields

symbolPoint :: forall r r. Lens (IpeSymbol r) (IpeSymbol r) (Point 2 r) (Point 2 r) Source #

data PathSegment r Source #

Example of an IpeSymbol. I.e. A symbol that expresses that the size is large sizeSymbol :: Attributes (AttrMapSym1 r) (SymbolAttributes r) sizeSymbol = attr SSize (IpeSize $ Named "large")

Paths

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

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

_EllipseSegment :: forall r. Prism' (PathSegment r) (Matrix 3 3 r) Source #

newtype Path r Source #

A path is a non-empty sequence of PathSegments.

Constructors

Path 

Instances

ToObject Path Source # 
Eq r => Eq (Path r) Source # 

Methods

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

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

Show r => Show (Path r) Source # 

Methods

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

show :: Path r -> String #

showList :: [Path r] -> ShowS #

Num r => IsTransformable (Path r) Source # 
Coordinate r => IpeRead (Path r) Source # 
Coordinate r => IpeReadText (Path r) Source # 
IpeWriteText r => IpeWrite (Path r) Source # 

Methods

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

IpeWriteText r => IpeWriteText (Path r) Source # 
type NumType (Path r) Source # 
type NumType (Path r) = r
type Dimension (Path r) Source # 
type Dimension (Path r) = 2

pathSegments :: forall r r. Iso (Path r) (Path r) (ViewL1 (PathSegment r)) (ViewL1 (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 

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

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

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

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

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

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

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

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

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

Attribute Mapping

type family AttrMap (r :: *) (l :: AttributeUniverse) :: * where ... Source #

The mapping between the labels of the the attributes and the types of the attributes with these labels. For example, the Matrix label/attribute should have a value of type 'Matrix 3 3 r'.

type AttrMapSym2 t t = AttrMap t t Source #

newtype Group r Source #

Groups and Objects

Group Attributes

A group is essentially a list of IpeObjects.

Constructors

Group 

Fields

Instances

ToObject Group Source # 
Eq r => Eq (Group r) Source # 

Methods

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

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

Show r => Show (Group r) Source # 

Methods

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

show :: Group r -> String #

showList :: [Group r] -> ShowS #

Num r => IsTransformable (Group r) Source # 
Coordinate r => IpeRead (Group r) Source # 
IpeWriteText r => IpeWrite (Group r) Source # 
type NumType (Group r) Source # 
type NumType (Group r) = r
type Dimension (Group r) Source # 
type Dimension (Group r) = 2

type Attributes' r = Attributes (AttrMapSym1 r) Source #

Attributes' :: * -> [AttributeUniverse] -> *

type IpeObject' g r = g r :+ IpeAttributes g r Source #

An IpeObject' is essentially the oject ogether with its attributes

groupItems :: forall r r. Iso (Group r) (Group r) [IpeObject r] [IpeObject r] Source #

data View Source #

The definition of a view make active layer into an index ?

Constructors

View 

Instances

data IpeStyle Source #

for now we pretty much ignore these

Constructors

IpeStyle 

data IpePage r Source #

An IpePage is essentially a Group, together with a list of layers and a list of views.

Constructors

IpePage 

Fields

Instances

views :: forall r. Lens' (IpePage r) [View] Source #

layers :: forall r. Lens' (IpePage r) [LayerName] Source #

content :: forall r r. Lens (IpePage r) (IpePage r) [IpeObject r] [IpeObject r] Source #

fromContent :: [IpeObject r] -> IpePage r Source #

Creates a simple page with no views.

data IpeFile r Source #

A complete ipe file

Constructors

IpeFile 

Instances

styles :: forall r. Lens' (IpeFile r) [IpeStyle] Source #

pages :: forall r r. Lens (IpeFile r) (IpeFile r) (NonEmpty (IpePage r)) (NonEmpty (IpePage r)) Source #

singlePageFile :: IpePage r -> IpeFile r Source #

Convenience function to construct an ipe file consisting of a single page.

singlePageFromContent :: [IpeObject r] -> IpeFile r Source #

Create a single page ipe file from a list of IpeObjects

applyMatrix' :: (IsTransformable (i r), Matrix AttributesOf i, Dimension (i r) ~ 2, r ~ NumType (i r)) => IpeObject' i r -> IpeObject' i r Source #

Takes and applies the ipe Matrix attribute of this item.

applyMatrix :: Num r => IpeObject r -> IpeObject r Source #

Applies the matrix to an ipe object if it has one.