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

Safe HaskellNone
LanguageHaskell2010

Data.Geometry.Ipe.Types

Contents

Synopsis

Documentation

newtype LayerName Source #

Constructors

LayerName 

Fields

Instances
Eq LayerName Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

Ord LayerName Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

Read LayerName Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

Show LayerName Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

IsString LayerName Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

IpeWrite LayerName Source # 
Instance details

Defined in Data.Geometry.Ipe.Writer

IpeWriteText LayerName Source # 
Instance details

Defined in Data.Geometry.Ipe.Writer

IpeRead LayerName Source # 
Instance details

Defined in Data.Geometry.Ipe.Reader

IpeReadText LayerName Source # 
Instance details

Defined in Data.Geometry.Ipe.Reader

data Image r Source #

Image Objects

Constructors

Image 

Fields

Instances
ToObject Image Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

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

Defined in Data.Geometry.Ipe.Types

Methods

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

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

Ord r => Ord (Image r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

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 # 
Instance details

Defined in Data.Geometry.Ipe.Types

Methods

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

show :: Image r -> String #

showList :: [Image r] -> ShowS #

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

Defined in Data.Geometry.Ipe.Types

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

Defined in Data.Geometry.Ipe.Writer

Coordinate r => IpeRead (Image r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Reader

type NumType (Image r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

type NumType (Image r) = r
type Dimension (Image r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

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 TextLabel r Source #

Text Objects

Constructors

Label Text (Point 2 r) 
Instances
ToObject TextLabel Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

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

Defined in Data.Geometry.Ipe.Types

Methods

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

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

Ord r => Ord (TextLabel r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

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

Defined in Data.Geometry.Ipe.Types

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

Defined in Data.Geometry.Ipe.Types

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

Defined in Data.Geometry.Ipe.Writer

Coordinate r => IpeRead (TextLabel r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Reader

type NumType (TextLabel r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

type NumType (TextLabel r) = r
type Dimension (TextLabel r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

type Dimension (TextLabel r) = 2

data MiniPage r Source #

Constructors

MiniPage Text (Point 2 r) r 
Instances
ToObject MiniPage Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

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

Defined in Data.Geometry.Ipe.Types

Methods

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

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

Ord r => Ord (MiniPage r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

Methods

compare :: MiniPage r -> MiniPage r -> Ordering #

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

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

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

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

max :: MiniPage r -> MiniPage r -> MiniPage r #

min :: MiniPage r -> MiniPage r -> MiniPage r #

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

Defined in Data.Geometry.Ipe.Types

Methods

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

show :: MiniPage r -> String #

showList :: [MiniPage r] -> ShowS #

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

Defined in Data.Geometry.Ipe.Types

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

Defined in Data.Geometry.Ipe.Writer

Coordinate r => IpeRead (MiniPage r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Reader

type NumType (MiniPage r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

type NumType (MiniPage r) = r
type Dimension (MiniPage r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

type Dimension (MiniPage r) = 2

data IpeSymbol r Source #

Ipe Symbols, i.e. Points

A symbol (point) in ipe

Constructors

Symbol 

Fields

Instances
ToObject IpeSymbol Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

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

Defined in Data.Geometry.Ipe.Types

Methods

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

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

Ord r => Ord (IpeSymbol r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

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

Defined in Data.Geometry.Ipe.Types

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

Defined in Data.Geometry.Ipe.Types

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

Defined in Data.Geometry.Ipe.Writer

Coordinate r => IpeRead (IpeSymbol r) Source #

Ipe read instances

Instance details

Defined in Data.Geometry.Ipe.Reader

type NumType (IpeSymbol r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

type NumType (IpeSymbol r) = r
type Dimension (IpeSymbol r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

type Dimension (IpeSymbol r) = 2

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:

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

Defined in Data.Geometry.Ipe.Types

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

Defined in Data.Geometry.Ipe.Types

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

Defined in Data.Geometry.Ipe.Types

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

Defined in Data.Geometry.Ipe.Writer

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

Defined in Data.Geometry.Ipe.Reader

type NumType (PathSegment r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

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

Defined in Data.Geometry.Ipe.Types

type Dimension (PathSegment r) = 2

_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 # 
Instance details

Defined in Data.Geometry.Ipe.Types

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

Defined in Data.Geometry.Ipe.Types

Methods

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

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

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

Defined in Data.Geometry.Ipe.Types

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.Types

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

(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

type NumType (Path r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

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

Defined in Data.Geometry.Ipe.Types

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 
Instances
Eq r => Eq (Operation r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

Methods

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

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

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

Defined in Data.Geometry.Ipe.Types

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

Defined in Data.Geometry.Ipe.Writer

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

Defined in Data.Geometry.Ipe.Reader

_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'.

newtype Group r Source #

Groups and Objects

Group Attributes

A group is essentially a list of IpeObjects.

Constructors

Group 

Fields

Instances
ToObject Group Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

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

Defined in Data.Geometry.Ipe.Types

Methods

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

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

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

Defined in Data.Geometry.Ipe.Types

Methods

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

show :: Group r -> String #

showList :: [Group r] -> ShowS #

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

Defined in Data.Geometry.Ipe.Types

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

Defined in Data.Geometry.Ipe.Writer

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

Defined in Data.Geometry.Ipe.Reader

type NumType (Group r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

type NumType (Group r) = r
type Dimension (Group r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

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

data IpeObject r Source #

Instances
Eq r => Eq (IpeObject r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

Methods

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

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

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

Defined in Data.Geometry.Ipe.Types

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

Defined in Data.Geometry.Ipe.Types

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

Defined in Data.Geometry.Ipe.Writer

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

Defined in Data.Geometry.Ipe.Reader

type NumType (IpeObject r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

type NumType (IpeObject r) = r
type Dimension (IpeObject r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

type Dimension (IpeObject r) = 2

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

class ToObject i where Source #

Minimal complete definition

ipeObject'

Methods

ipeObject' :: i r -> IpeAttributes i r -> IpeObject r Source #

flattenGroups :: [IpeObject r] -> [IpeObject r] Source #

collect all non-group objects

data View Source #

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

Constructors

View 
Instances
Eq View Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

Methods

(==) :: View -> View -> Bool #

(/=) :: View -> View -> Bool #

Ord View Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

Methods

compare :: View -> View -> Ordering #

(<) :: View -> View -> Bool #

(<=) :: View -> View -> Bool #

(>) :: View -> View -> Bool #

(>=) :: View -> View -> Bool #

max :: View -> View -> View #

min :: View -> View -> View #

Show View Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

Methods

showsPrec :: Int -> View -> ShowS #

show :: View -> String #

showList :: [View] -> ShowS #

IpeWrite View Source # 
Instance details

Defined in Data.Geometry.Ipe.Writer

IpeRead View Source # 
Instance details

Defined in Data.Geometry.Ipe.Reader

data IpeStyle Source #

for now we pretty much ignore these

Constructors

IpeStyle 
Instances
Eq IpeStyle Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

Show IpeStyle Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

IpeWrite IpeStyle Source # 
Instance details

Defined in Data.Geometry.Ipe.Writer

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
Eq r => Eq (IpePage r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

Methods

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

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

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

Defined in Data.Geometry.Ipe.Types

Methods

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

show :: IpePage r -> String #

showList :: [IpePage r] -> ShowS #

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

Defined in Data.Geometry.Ipe.Writer

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

Defined in Data.Geometry.Ipe.Reader

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
Eq r => Eq (IpeFile r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Types

Methods

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

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

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

Defined in Data.Geometry.Ipe.Types

Methods

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

show :: IpeFile r -> String #

showList :: [IpeFile r] -> ShowS #

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

Defined in Data.Geometry.Ipe.Writer

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

Defined in Data.Geometry.Ipe.Reader

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 :: Fractional r => IpeObject r -> IpeObject r Source #

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