Copyright | (C) Frank Staals |
---|---|
License | see the LICENSE file |
Maintainer | Frank Staals |
Safe Haskell | None |
Language | Haskell2010 |
Data type modeling the various elements in Ipe files.
Synopsis
- newtype LayerName = LayerName {
- _layerName :: Text
- data Image r = Image {
- _imageData :: ()
- _rect :: Rectangle () r
- rect :: forall r r. Lens (Image r) (Image r) (Rectangle () r) (Rectangle () r)
- imageData :: forall r. Lens' (Image r) ()
- data TextLabel r = Label Text (Point 2 r)
- data MiniPage r = MiniPage Text (Point 2 r) r
- width :: MiniPage t -> t
- data IpeSymbol r = Symbol {
- _symbolPoint :: Point 2 r
- _symbolName :: Text
- symbolPoint :: forall r r. Lens (IpeSymbol r) (IpeSymbol r) (Point 2 r) (Point 2 r)
- symbolName :: forall r. Lens' (IpeSymbol r) Text
- data PathSegment r
- = PolyLineSegment (PolyLine 2 () r)
- | PolygonPath (SimplePolygon () r)
- | CubicBezierSegment
- | QuadraticBezierSegment
- | EllipseSegment (Matrix 3 3 r)
- | ArcSegment
- | SplineSegment
- | ClosedSplineSegment
- _ClosedSplineSegment :: forall r. Prism' (PathSegment r) ()
- _SplineSegment :: forall r. Prism' (PathSegment r) ()
- _ArcSegment :: forall r. Prism' (PathSegment r) ()
- _EllipseSegment :: forall r. Prism' (PathSegment r) (Matrix 3 3 r)
- _QuadraticBezierSegment :: forall r. Prism' (PathSegment r) ()
- _CubicBezierSegment :: forall r. Prism' (PathSegment r) ()
- _PolygonPath :: forall r. Prism' (PathSegment r) (SimplePolygon () r)
- _PolyLineSegment :: forall r. Prism' (PathSegment r) (PolyLine 2 () r)
- newtype Path r = Path {
- _pathSegments :: LSeq 1 (PathSegment r)
- pathSegments :: forall r r. Iso (Path r) (Path r) (LSeq 1 (PathSegment r)) (LSeq 1 (PathSegment r))
- data Operation r
- _ClosePath :: forall r. Prism' (Operation r) ()
- _ClosedSpline :: forall r. Prism' (Operation r) [Point 2 r]
- _Spline :: forall r. Prism' (Operation r) [Point 2 r]
- _ArcTo :: forall r. Prism' (Operation r) (Matrix 3 3 r, Point 2 r)
- _Ellipse :: forall r. Prism' (Operation r) (Matrix 3 3 r)
- _QCurveTo :: forall r. Prism' (Operation r) (Point 2 r, Point 2 r)
- _CurveTo :: forall r. Prism' (Operation r) (Point 2 r, Point 2 r, Point 2 r)
- _LineTo :: forall r. Prism' (Operation r) (Point 2 r)
- _MoveTo :: forall r. Prism' (Operation r) (Point 2 r)
- type family AttrMap (r :: *) (l :: AttributeUniverse) :: * where ...
- type AttrMapSym2 (r6989586621679226030 :: Type) (l6989586621679226031 :: AttributeUniverse) = AttrMap r6989586621679226030 l6989586621679226031
- data AttrMapSym1 (r6989586621679226030 :: Type) :: (~>) AttributeUniverse Type where
- AttrMapSym1KindInference :: forall r6989586621679226030 l6989586621679226031 arg. SameKind (Apply (AttrMapSym1 r6989586621679226030) arg) (AttrMapSym2 r6989586621679226030 arg) => AttrMapSym1 r6989586621679226030 l6989586621679226031
- data AttrMapSym0 :: (~>) Type ((~>) AttributeUniverse Type) where
- AttrMapSym0KindInference :: forall r6989586621679226030 arg. SameKind (Apply AttrMapSym0 arg) (AttrMapSym1 arg) => AttrMapSym0 r6989586621679226030
- newtype Group r = Group [IpeObject r]
- type family AttributesOf (t :: * -> *) :: [u] where ...
- type Attributes' r = Attributes (AttrMapSym1 r)
- type IpeAttributes g r = Attributes' r (AttributesOf g)
- type IpeObject' g r = g r :+ IpeAttributes g r
- attributes :: Lens' (IpeObject' g r) (IpeAttributes g r)
- data IpeObject r
- = IpeGroup (IpeObject' Group r)
- | IpeImage (IpeObject' Image r)
- | IpeTextLabel (IpeObject' TextLabel r)
- | IpeMiniPage (IpeObject' MiniPage r)
- | IpeUse (IpeObject' IpeSymbol r)
- | IpePath (IpeObject' Path r)
- _IpePath :: forall r. Prism' (IpeObject r) (IpeObject' Path r)
- _IpeUse :: forall r. Prism' (IpeObject r) (IpeObject' IpeSymbol r)
- _IpeMiniPage :: forall r. Prism' (IpeObject r) (IpeObject' MiniPage r)
- _IpeTextLabel :: forall r. Prism' (IpeObject r) (IpeObject' TextLabel r)
- _IpeImage :: forall r. Prism' (IpeObject r) (IpeObject' Image r)
- _IpeGroup :: forall r. Prism' (IpeObject r) (IpeObject' Group r)
- groupItems :: Lens (Group r) (Group s) [IpeObject r] [IpeObject s]
- class ToObject i where
- mkIpeObject :: IpeObject' i r -> IpeObject r
- ipeObject' :: ToObject i => i r -> IpeAttributes i r -> IpeObject r
- commonAttributes :: Lens' (IpeObject r) (Attributes (AttrMapSym1 r) CommonAttributes)
- flattenGroups :: [IpeObject r] -> [IpeObject r]
- data View = View {}
- layerNames :: Lens' View [LayerName]
- activeLayer :: Lens' View LayerName
- data IpeStyle = IpeStyle {
- _styleName :: Maybe Text
- _styleData :: Node Text Text
- styleName :: Lens' IpeStyle (Maybe Text)
- styleData :: Lens' IpeStyle (Node Text Text)
- basicIpeStyle :: IpeStyle
- data IpePreamble = IpePreamble {
- _encoding :: Maybe Text
- _preambleData :: Text
- preambleData :: Lens' IpePreamble Text
- encoding :: Lens' IpePreamble (Maybe Text)
- type IpeBitmap = Text
- data IpePage r = IpePage {}
- views :: forall r. Lens' (IpePage r) [View]
- layers :: forall r. Lens' (IpePage r) [LayerName]
- content :: forall r r. Lens (IpePage r) (IpePage r) [IpeObject r] [IpeObject r]
- fromContent :: [IpeObject r] -> IpePage r
- data IpeFile r = IpeFile {}
- styles :: forall r. Lens' (IpeFile r) [IpeStyle]
- preamble :: forall r. Lens' (IpeFile r) (Maybe IpePreamble)
- pages :: forall r r. Lens (IpeFile r) (IpeFile r) (NonEmpty (IpePage r)) (NonEmpty (IpePage r))
- singlePageFile :: IpePage r -> IpeFile r
- singlePageFromContent :: [IpeObject r] -> IpeFile r
- applyMatrix' :: (IsTransformable (i r), Matrix ∈ AttributesOf i, Dimension (i r) ~ 2, r ~ NumType (i r)) => IpeObject' i r -> IpeObject' i r
- applyMatrix :: Fractional r => IpeObject r -> IpeObject r
- applyMatrices :: Fractional r => IpeFile r -> IpeFile r
- applyMatricesPage :: Fractional r => IpePage r -> IpePage r
Documentation
Instances
Eq LayerName Source # | |
Ord LayerName Source # | |
Defined in Data.Geometry.Ipe.Types | |
Read LayerName Source # | |
Show LayerName Source # | |
IsString LayerName Source # | |
Defined in Data.Geometry.Ipe.Types fromString :: String -> LayerName # | |
IpeRead LayerName Source # | |
Defined in Data.Geometry.Ipe.Reader | |
IpeReadText LayerName Source # | |
Defined in Data.Geometry.Ipe.Reader | |
IpeWrite LayerName Source # | |
IpeWriteText LayerName Source # | |
Defined in Data.Geometry.Ipe.Writer |
Image Objects
Image | |
|
Instances
ToObject Image Source # | |
Defined in Data.Geometry.Ipe.Types mkIpeObject :: IpeObject' Image r -> IpeObject r Source # | |
Eq r => Eq (Image r) Source # | |
Ord r => Ord (Image r) Source # | |
Show r => Show (Image r) Source # | |
Fractional r => IsTransformable (Image r) Source # | |
Defined in Data.Geometry.Ipe.Types transformBy :: Transformation (Dimension (Image r)) (NumType (Image r)) -> Image r -> Image r # | |
Coordinate r => IpeRead (Image r) Source # | |
Defined in Data.Geometry.Ipe.Reader | |
IpeWriteText r => IpeWrite (Image r) Source # | |
type Dimension (Image r) Source # | |
Defined in Data.Geometry.Ipe.Types | |
type NumType (Image r) Source # | |
Defined in Data.Geometry.Ipe.Types |
Text Objects
Instances
ToObject TextLabel Source # | |
Defined in Data.Geometry.Ipe.Types mkIpeObject :: IpeObject' TextLabel r -> IpeObject r Source # | |
Eq r => Eq (TextLabel r) Source # | |
Ord r => Ord (TextLabel r) Source # | |
Defined in Data.Geometry.Ipe.Types | |
Show r => Show (TextLabel r) Source # | |
Fractional r => IsTransformable (TextLabel r) Source # | |
Defined in Data.Geometry.Ipe.Types transformBy :: Transformation (Dimension (TextLabel r)) (NumType (TextLabel r)) -> TextLabel r -> TextLabel r # | |
Coordinate r => IpeRead (TextLabel r) Source # | |
Defined in Data.Geometry.Ipe.Reader | |
IpeWriteText r => IpeWrite (TextLabel r) Source # | |
type Dimension (TextLabel r) Source # | |
Defined in Data.Geometry.Ipe.Types | |
type NumType (TextLabel r) Source # | |
Defined in Data.Geometry.Ipe.Types |
Instances
ToObject MiniPage Source # | |
Defined in Data.Geometry.Ipe.Types mkIpeObject :: IpeObject' MiniPage r -> IpeObject r Source # | |
Eq r => Eq (MiniPage r) Source # | |
Ord r => Ord (MiniPage r) Source # | |
Show r => Show (MiniPage r) Source # | |
Fractional r => IsTransformable (MiniPage r) Source # | |
Defined in Data.Geometry.Ipe.Types transformBy :: Transformation (Dimension (MiniPage r)) (NumType (MiniPage r)) -> MiniPage r -> MiniPage r # | |
Coordinate r => IpeRead (MiniPage r) Source # | |
Defined in Data.Geometry.Ipe.Reader | |
IpeWriteText r => IpeWrite (MiniPage r) Source # | |
type Dimension (MiniPage r) Source # | |
Defined in Data.Geometry.Ipe.Types | |
type NumType (MiniPage r) Source # | |
Defined in Data.Geometry.Ipe.Types |
Ipe Symbols, i.e. Points
A symbol (point) in ipe
Symbol | |
|
Instances
ToObject IpeSymbol Source # | |
Defined in Data.Geometry.Ipe.Types mkIpeObject :: IpeObject' IpeSymbol r -> IpeObject r Source # | |
Eq r => Eq (IpeSymbol r) Source # | |
Ord r => Ord (IpeSymbol r) Source # | |
Defined in Data.Geometry.Ipe.Types | |
Show r => Show (IpeSymbol r) Source # | |
Fractional r => IsTransformable (IpeSymbol r) Source # | |
Defined in Data.Geometry.Ipe.Types transformBy :: Transformation (Dimension (IpeSymbol r)) (NumType (IpeSymbol r)) -> IpeSymbol r -> IpeSymbol r # | |
Coordinate r => IpeRead (IpeSymbol r) Source # | Ipe read instances |
Defined in Data.Geometry.Ipe.Reader | |
IpeWriteText r => IpeWrite (IpeSymbol r) Source # | |
type Dimension (IpeSymbol r) Source # | |
Defined in Data.Geometry.Ipe.Types | |
type NumType (IpeSymbol r) Source # | |
Defined in Data.Geometry.Ipe.Types |
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:
PolyLineSegment (PolyLine 2 () r) | |
PolygonPath (SimplePolygon () r) | |
CubicBezierSegment | |
QuadraticBezierSegment | |
EllipseSegment (Matrix 3 3 r) | |
ArcSegment | |
SplineSegment | |
ClosedSplineSegment |
Instances
_ClosedSplineSegment :: forall r. Prism' (PathSegment r) () Source #
_SplineSegment :: forall r. Prism' (PathSegment r) () Source #
_ArcSegment :: forall r. Prism' (PathSegment r) () Source #
_EllipseSegment :: forall r. Prism' (PathSegment r) (Matrix 3 3 r) Source #
_QuadraticBezierSegment :: forall r. Prism' (PathSegment r) () Source #
_CubicBezierSegment :: forall r. Prism' (PathSegment r) () Source #
_PolygonPath :: forall r. Prism' (PathSegment r) (SimplePolygon () r) Source #
_PolyLineSegment :: forall r. Prism' (PathSegment r) (PolyLine 2 () r) Source #
A path is a non-empty sequence of PathSegments.
Path | |
|
Instances
ToObject Path Source # | |
Defined in Data.Geometry.Ipe.Types mkIpeObject :: IpeObject' Path r -> IpeObject r Source # | |
Eq r => Eq (Path r) Source # | |
Show r => Show (Path r) Source # | |
Fractional r => IsTransformable (Path r) Source # | |
Defined in Data.Geometry.Ipe.Types transformBy :: Transformation (Dimension (Path r)) (NumType (Path r)) -> Path r -> Path r # | |
(Coordinate r, Eq r) => IpeRead (Path r) Source # | |
Defined in Data.Geometry.Ipe.Reader | |
(Coordinate r, Eq r) => IpeReadText (Path r) Source # | |
Defined in Data.Geometry.Ipe.Reader ipeReadText :: Text -> Either ConversionError (Path r) Source # | |
IpeWriteText r => IpeWrite (Path r) Source # | |
IpeWriteText r => IpeWriteText (Path r) Source # | |
Defined in Data.Geometry.Ipe.Writer | |
type Dimension (Path r) Source # | |
Defined in Data.Geometry.Ipe.Types | |
type NumType (Path r) Source # | |
Defined in Data.Geometry.Ipe.Types |
pathSegments :: forall r r. Iso (Path r) (Path r) (LSeq 1 (PathSegment r)) (LSeq 1 (PathSegment r)) Source #
type that represents a path in ipe.
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 # | |
Show r => Show (Operation r) Source # | |
Coordinate r => IpeReadText [Operation r] Source # | |
Defined in Data.Geometry.Ipe.Reader ipeReadText :: Text -> Either ConversionError [Operation r] Source # | |
IpeWriteText r => IpeWriteText (Operation r) Source # | |
Defined in Data.Geometry.Ipe.Writer |
_ClosePath :: forall r. Prism' (Operation 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'.
AttrMap r Layer = LayerName | |
AttrMap r Matrix = Matrix 3 3 r | |
AttrMap r Pin = PinType | |
AttrMap r Transformations = TransformationTypes | |
AttrMap r Stroke = IpeColor r | |
AttrMap r Pen = IpePen r | |
AttrMap r Fill = IpeColor r | |
AttrMap r Size = IpeSize r | |
AttrMap r Dash = IpeDash r | |
AttrMap r LineCap = Int | |
AttrMap r LineJoin = Int | |
AttrMap r FillRule = FillType | |
AttrMap r Arrow = IpeArrow r | |
AttrMap r RArrow = IpeArrow r | |
AttrMap r Opacity = IpeOpacity | |
AttrMap r Tiling = IpeTiling | |
AttrMap r Gradient = IpeGradient | |
AttrMap r Clip = Path r |
type AttrMapSym2 (r6989586621679226030 :: Type) (l6989586621679226031 :: AttributeUniverse) = AttrMap r6989586621679226030 l6989586621679226031 Source #
data AttrMapSym1 (r6989586621679226030 :: Type) :: (~>) AttributeUniverse Type where Source #
AttrMapSym1KindInference :: forall r6989586621679226030 l6989586621679226031 arg. SameKind (Apply (AttrMapSym1 r6989586621679226030) arg) (AttrMapSym2 r6989586621679226030 arg) => AttrMapSym1 r6989586621679226030 l6989586621679226031 |
Instances
SuppressUnusedWarnings (AttrMapSym1 r6989586621679226030 :: TyFun AttributeUniverse Type -> Type) Source # | |
Defined in Data.Geometry.Ipe.Types suppressUnusedWarnings :: () # | |
type Apply (AttrMapSym1 r6989586621679226030 :: TyFun AttributeUniverse Type -> Type) (l6989586621679226031 :: AttributeUniverse) Source # | |
Defined in Data.Geometry.Ipe.Types type Apply (AttrMapSym1 r6989586621679226030 :: TyFun AttributeUniverse Type -> Type) (l6989586621679226031 :: AttributeUniverse) = AttrMap r6989586621679226030 l6989586621679226031 |
data AttrMapSym0 :: (~>) Type ((~>) AttributeUniverse Type) where Source #
AttrMapSym0KindInference :: forall r6989586621679226030 arg. SameKind (Apply AttrMapSym0 arg) (AttrMapSym1 arg) => AttrMapSym0 r6989586621679226030 |
Instances
SuppressUnusedWarnings AttrMapSym0 Source # | |
Defined in Data.Geometry.Ipe.Types suppressUnusedWarnings :: () # | |
type Apply AttrMapSym0 (r6989586621679226030 :: Type) Source # | |
Defined in Data.Geometry.Ipe.Types |
Groups and Objects
Group Attributes
A group is essentially a list of IpeObjects.
Instances
ToObject Group Source # | |
Defined in Data.Geometry.Ipe.Types mkIpeObject :: IpeObject' Group r -> IpeObject r Source # | |
Eq r => Eq (Group r) Source # | |
Show r => Show (Group r) Source # | |
Fractional r => IsTransformable (Group r) Source # | |
Defined in Data.Geometry.Ipe.Types transformBy :: Transformation (Dimension (Group r)) (NumType (Group r)) -> Group r -> Group r # | |
(Coordinate r, Eq r) => IpeRead (Group r) Source # | |
Defined in Data.Geometry.Ipe.Reader | |
IpeWriteText r => IpeWrite (Group r) Source # | |
type Dimension (Group r) Source # | |
Defined in Data.Geometry.Ipe.Types | |
type NumType (Group r) Source # | |
Defined in Data.Geometry.Ipe.Types |
type family AttributesOf (t :: * -> *) :: [u] where ... Source #
type Attributes' r = Attributes (AttrMapSym1 r) Source #
Attributes' :: * -> [AttributeUniverse] -> *
type IpeAttributes g r = Attributes' r (AttributesOf g) Source #
type IpeObject' g r = g r :+ IpeAttributes g r Source #
An IpeObject' is essentially the oject ogether with its attributes
attributes :: Lens' (IpeObject' g r) (IpeAttributes g r) Source #
IpeGroup (IpeObject' Group r) | |
IpeImage (IpeObject' Image r) | |
IpeTextLabel (IpeObject' TextLabel r) | |
IpeMiniPage (IpeObject' MiniPage r) | |
IpeUse (IpeObject' IpeSymbol r) | |
IpePath (IpeObject' Path r) |
Instances
Eq r => Eq (IpeObject r) Source # | |
Show r => Show (IpeObject r) Source # | |
Fractional r => IsTransformable (IpeObject r) Source # | |
Defined in Data.Geometry.Ipe.Types transformBy :: Transformation (Dimension (IpeObject r)) (NumType (IpeObject r)) -> IpeObject r -> IpeObject r # | |
(Coordinate r, Eq r) => IpeRead (IpeObject r) Source # | |
Defined in Data.Geometry.Ipe.Reader | |
IpeWriteText r => IpeWrite (IpeObject r) Source # | |
type Dimension (IpeObject r) Source # | |
Defined in Data.Geometry.Ipe.Types | |
type NumType (IpeObject r) Source # | |
Defined in Data.Geometry.Ipe.Types |
_IpeMiniPage :: forall r. Prism' (IpeObject r) (IpeObject' MiniPage r) Source #
_IpeTextLabel :: forall r. Prism' (IpeObject r) (IpeObject' TextLabel r) Source #
class ToObject i where Source #
mkIpeObject :: IpeObject' i r -> IpeObject r Source #
Instances
ToObject Image Source # | |
Defined in Data.Geometry.Ipe.Types mkIpeObject :: IpeObject' Image r -> IpeObject r Source # | |
ToObject IpeSymbol Source # | |
Defined in Data.Geometry.Ipe.Types mkIpeObject :: IpeObject' IpeSymbol r -> IpeObject r Source # | |
ToObject MiniPage Source # | |
Defined in Data.Geometry.Ipe.Types mkIpeObject :: IpeObject' MiniPage r -> IpeObject r Source # | |
ToObject TextLabel Source # | |
Defined in Data.Geometry.Ipe.Types mkIpeObject :: IpeObject' TextLabel r -> IpeObject r Source # | |
ToObject Path Source # | |
Defined in Data.Geometry.Ipe.Types mkIpeObject :: IpeObject' Path r -> IpeObject r Source # | |
ToObject Group Source # | |
Defined in Data.Geometry.Ipe.Types mkIpeObject :: IpeObject' Group r -> IpeObject r Source # |
ipeObject' :: ToObject i => i r -> IpeAttributes i r -> IpeObject r Source #
Shorthand for constructing ipeObjects
commonAttributes :: Lens' (IpeObject r) (Attributes (AttrMapSym1 r) CommonAttributes) Source #
flattenGroups :: [IpeObject r] -> [IpeObject r] Source #
collect all non-group objects
The definition of a view make active layer into an index ?
View | |
|
for now we pretty much ignore these
IpeStyle | |
|
data IpePreamble Source #
The maybe string is the encoding
Instances
Eq IpePreamble Source # | |
Defined in Data.Geometry.Ipe.Types (==) :: IpePreamble -> IpePreamble -> Bool # (/=) :: IpePreamble -> IpePreamble -> Bool # | |
Ord IpePreamble Source # | |
Defined in Data.Geometry.Ipe.Types compare :: IpePreamble -> IpePreamble -> Ordering # (<) :: IpePreamble -> IpePreamble -> Bool # (<=) :: IpePreamble -> IpePreamble -> Bool # (>) :: IpePreamble -> IpePreamble -> Bool # (>=) :: IpePreamble -> IpePreamble -> Bool # max :: IpePreamble -> IpePreamble -> IpePreamble # min :: IpePreamble -> IpePreamble -> IpePreamble # | |
Read IpePreamble Source # | |
Defined in Data.Geometry.Ipe.Types readsPrec :: Int -> ReadS IpePreamble # readList :: ReadS [IpePreamble] # readPrec :: ReadPrec IpePreamble # readListPrec :: ReadPrec [IpePreamble] # | |
Show IpePreamble Source # | |
Defined in Data.Geometry.Ipe.Types showsPrec :: Int -> IpePreamble -> ShowS # show :: IpePreamble -> String # showList :: [IpePreamble] -> ShowS # | |
IpeWrite IpePreamble Source # | |
Defined in Data.Geometry.Ipe.Writer |
An IpePage is essentially a Group, together with a list of layers and a list of views.
fromContent :: [IpeObject r] -> IpePage r Source #
Creates a simple page with no views.
A complete ipe file
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.
applyMatrices :: Fractional r => IpeFile r -> IpeFile r Source #
applyMatricesPage :: Fractional r => IpePage r -> IpePage r Source #