hgeometry-ipe-0.13: Reading and Writing ipe7 files.
Safe HaskellNone
LanguageHaskell2010

Ipe.Content

Synopsis

Documentation

data Image r Source #

Image Objects

Constructors

Image () (Rectangle () r) 

Instances

Instances details
Functor Image Source # 
Instance details

Defined in Ipe.Content

Methods

fmap :: (a -> b) -> Image a -> Image b #

(<$) :: a -> Image b -> Image a #

Foldable Image Source # 
Instance details

Defined in Ipe.Content

Methods

fold :: Monoid m => Image m -> m #

foldMap :: Monoid m => (a -> m) -> Image a -> m #

foldMap' :: Monoid m => (a -> m) -> Image a -> m #

foldr :: (a -> b -> b) -> b -> Image a -> b #

foldr' :: (a -> b -> b) -> b -> Image a -> b #

foldl :: (b -> a -> b) -> b -> Image a -> b #

foldl' :: (b -> a -> b) -> b -> Image a -> b #

foldr1 :: (a -> a -> a) -> Image a -> a #

foldl1 :: (a -> a -> a) -> Image a -> a #

toList :: Image a -> [a] #

null :: Image a -> Bool #

length :: Image a -> Int #

elem :: Eq a => a -> Image a -> Bool #

maximum :: Ord a => Image a -> a #

minimum :: Ord a => Image a -> a #

sum :: Num a => Image a -> a #

product :: Num a => Image a -> a #

Traversable Image Source # 
Instance details

Defined in Ipe.Content

Methods

traverse :: Applicative f => (a -> f b) -> Image a -> f (Image b) #

sequenceA :: Applicative f => Image (f a) -> f (Image a) #

mapM :: Monad m => (a -> m b) -> Image a -> m (Image b) #

sequence :: Monad m => Image (m a) -> m (Image a) #

ToObject Image Source # 
Instance details

Defined in Ipe.Content

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

Defined in Ipe.Content

Methods

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

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

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

Defined in Ipe.Content

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 Ipe.Content

Methods

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

show :: Image r -> String #

showList :: [Image r] -> ShowS #

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

Defined in Ipe.Content

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

Defined in Ipe.Reader

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

Defined in Ipe.Writer

type Dimension (Image r) Source # 
Instance details

Defined in Ipe.Content

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

Defined in Ipe.Content

type NumType (Image r) = r

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

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

data TextLabel r Source #

Text Objects

Constructors

Label Text (Point 2 r) 

Instances

Instances details
Functor TextLabel Source # 
Instance details

Defined in Ipe.Content

Methods

fmap :: (a -> b) -> TextLabel a -> TextLabel b #

(<$) :: a -> TextLabel b -> TextLabel a #

Foldable TextLabel Source # 
Instance details

Defined in Ipe.Content

Methods

fold :: Monoid m => TextLabel m -> m #

foldMap :: Monoid m => (a -> m) -> TextLabel a -> m #

foldMap' :: Monoid m => (a -> m) -> TextLabel a -> m #

foldr :: (a -> b -> b) -> b -> TextLabel a -> b #

foldr' :: (a -> b -> b) -> b -> TextLabel a -> b #

foldl :: (b -> a -> b) -> b -> TextLabel a -> b #

foldl' :: (b -> a -> b) -> b -> TextLabel a -> b #

foldr1 :: (a -> a -> a) -> TextLabel a -> a #

foldl1 :: (a -> a -> a) -> TextLabel a -> a #

toList :: TextLabel a -> [a] #

null :: TextLabel a -> Bool #

length :: TextLabel a -> Int #

elem :: Eq a => a -> TextLabel a -> Bool #

maximum :: Ord a => TextLabel a -> a #

minimum :: Ord a => TextLabel a -> a #

sum :: Num a => TextLabel a -> a #

product :: Num a => TextLabel a -> a #

Traversable TextLabel Source # 
Instance details

Defined in Ipe.Content

Methods

traverse :: Applicative f => (a -> f b) -> TextLabel a -> f (TextLabel b) #

sequenceA :: Applicative f => TextLabel (f a) -> f (TextLabel a) #

mapM :: Monad m => (a -> m b) -> TextLabel a -> m (TextLabel b) #

sequence :: Monad m => TextLabel (m a) -> m (TextLabel a) #

ToObject TextLabel Source # 
Instance details

Defined in Ipe.Content

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

Defined in Ipe.Content

Methods

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

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

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

Defined in Ipe.Content

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

Defined in Ipe.Content

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

Defined in Ipe.Content

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

Defined in Ipe.Reader

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

Defined in Ipe.Writer

type Dimension (TextLabel r) Source # 
Instance details

Defined in Ipe.Content

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

Defined in Ipe.Content

type NumType (TextLabel r) = r

data MiniPage r Source #

Constructors

MiniPage Text (Point 2 r) r 

Instances

Instances details
Functor MiniPage Source # 
Instance details

Defined in Ipe.Content

Methods

fmap :: (a -> b) -> MiniPage a -> MiniPage b #

(<$) :: a -> MiniPage b -> MiniPage a #

Foldable MiniPage Source # 
Instance details

Defined in Ipe.Content

Methods

fold :: Monoid m => MiniPage m -> m #

foldMap :: Monoid m => (a -> m) -> MiniPage a -> m #

foldMap' :: Monoid m => (a -> m) -> MiniPage a -> m #

foldr :: (a -> b -> b) -> b -> MiniPage a -> b #

foldr' :: (a -> b -> b) -> b -> MiniPage a -> b #

foldl :: (b -> a -> b) -> b -> MiniPage a -> b #

foldl' :: (b -> a -> b) -> b -> MiniPage a -> b #

foldr1 :: (a -> a -> a) -> MiniPage a -> a #

foldl1 :: (a -> a -> a) -> MiniPage a -> a #

toList :: MiniPage a -> [a] #

null :: MiniPage a -> Bool #

length :: MiniPage a -> Int #

elem :: Eq a => a -> MiniPage a -> Bool #

maximum :: Ord a => MiniPage a -> a #

minimum :: Ord a => MiniPage a -> a #

sum :: Num a => MiniPage a -> a #

product :: Num a => MiniPage a -> a #

Traversable MiniPage Source # 
Instance details

Defined in Ipe.Content

Methods

traverse :: Applicative f => (a -> f b) -> MiniPage a -> f (MiniPage b) #

sequenceA :: Applicative f => MiniPage (f a) -> f (MiniPage a) #

mapM :: Monad m => (a -> m b) -> MiniPage a -> m (MiniPage b) #

sequence :: Monad m => MiniPage (m a) -> m (MiniPage a) #

ToObject MiniPage Source # 
Instance details

Defined in Ipe.Content

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

Defined in Ipe.Content

Methods

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

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

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

Defined in Ipe.Content

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 Ipe.Content

Methods

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

show :: MiniPage r -> String #

showList :: [MiniPage r] -> ShowS #

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

Defined in Ipe.Content

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

Defined in Ipe.Reader

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

Defined in Ipe.Writer

type Dimension (MiniPage r) Source # 
Instance details

Defined in Ipe.Content

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

Defined in Ipe.Content

type NumType (MiniPage r) = r

data IpeSymbol r Source #

Ipe Symbols, i.e. Points

A symbol (point) in ipe

Constructors

Symbol (Point 2 r) Text 

Instances

Instances details
Functor IpeSymbol Source # 
Instance details

Defined in Ipe.Content

Methods

fmap :: (a -> b) -> IpeSymbol a -> IpeSymbol b #

(<$) :: a -> IpeSymbol b -> IpeSymbol a #

Foldable IpeSymbol Source # 
Instance details

Defined in Ipe.Content

Methods

fold :: Monoid m => IpeSymbol m -> m #

foldMap :: Monoid m => (a -> m) -> IpeSymbol a -> m #

foldMap' :: Monoid m => (a -> m) -> IpeSymbol a -> m #

foldr :: (a -> b -> b) -> b -> IpeSymbol a -> b #

foldr' :: (a -> b -> b) -> b -> IpeSymbol a -> b #

foldl :: (b -> a -> b) -> b -> IpeSymbol a -> b #

foldl' :: (b -> a -> b) -> b -> IpeSymbol a -> b #

foldr1 :: (a -> a -> a) -> IpeSymbol a -> a #

foldl1 :: (a -> a -> a) -> IpeSymbol a -> a #

toList :: IpeSymbol a -> [a] #

null :: IpeSymbol a -> Bool #

length :: IpeSymbol a -> Int #

elem :: Eq a => a -> IpeSymbol a -> Bool #

maximum :: Ord a => IpeSymbol a -> a #

minimum :: Ord a => IpeSymbol a -> a #

sum :: Num a => IpeSymbol a -> a #

product :: Num a => IpeSymbol a -> a #

Traversable IpeSymbol Source # 
Instance details

Defined in Ipe.Content

Methods

traverse :: Applicative f => (a -> f b) -> IpeSymbol a -> f (IpeSymbol b) #

sequenceA :: Applicative f => IpeSymbol (f a) -> f (IpeSymbol a) #

mapM :: Monad m => (a -> m b) -> IpeSymbol a -> m (IpeSymbol b) #

sequence :: Monad m => IpeSymbol (m a) -> m (IpeSymbol a) #

ToObject IpeSymbol Source # 
Instance details

Defined in Ipe.Content

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

Defined in Ipe.Content

Methods

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

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

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

Defined in Ipe.Content

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

Defined in Ipe.Content

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

Defined in Ipe.Content

Coordinate r => IpeRead (IpeSymbol r) Source #

Ipe read instances

Instance details

Defined in Ipe.Reader

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

Defined in Ipe.Writer

type Dimension (IpeSymbol r) Source # 
Instance details

Defined in Ipe.Content

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

Defined in Ipe.Content

type NumType (IpeSymbol r) = r

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

newtype Path r Source #

A path is a non-empty sequence of PathSegments.

Constructors

Path (LSeq 1 (PathSegment r)) 

Instances

Instances details
Functor Path Source # 
Instance details

Defined in Ipe.Path

Methods

fmap :: (a -> b) -> Path a -> Path b #

(<$) :: a -> Path b -> Path a #

Foldable Path Source # 
Instance details

Defined in Ipe.Path

Methods

fold :: Monoid m => Path m -> m #

foldMap :: Monoid m => (a -> m) -> Path a -> m #

foldMap' :: Monoid m => (a -> m) -> Path a -> m #

foldr :: (a -> b -> b) -> b -> Path a -> b #

foldr' :: (a -> b -> b) -> b -> Path a -> b #

foldl :: (b -> a -> b) -> b -> Path a -> b #

foldl' :: (b -> a -> b) -> b -> Path a -> b #

foldr1 :: (a -> a -> a) -> Path a -> a #

foldl1 :: (a -> a -> a) -> Path a -> a #

toList :: Path a -> [a] #

null :: Path a -> Bool #

length :: Path a -> Int #

elem :: Eq a => a -> Path a -> Bool #

maximum :: Ord a => Path a -> a #

minimum :: Ord a => Path a -> a #

sum :: Num a => Path a -> a #

product :: Num a => Path a -> a #

Traversable Path Source # 
Instance details

Defined in Ipe.Path

Methods

traverse :: Applicative f => (a -> f b) -> Path a -> f (Path b) #

sequenceA :: Applicative f => Path (f a) -> f (Path a) #

mapM :: Monad m => (a -> m b) -> Path a -> m (Path b) #

sequence :: Monad m => Path (m a) -> m (Path a) #

ToObject Path Source # 
Instance details

Defined in Ipe.Content

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

Defined in Ipe.Path

Methods

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

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

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

Defined in Ipe.Path

Methods

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

show :: Path r -> String #

showList :: [Path r] -> ShowS #

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

Defined in Ipe.Path

Methods

transformBy :: Transformation (Dimension (Path r)) (NumType (Path r)) -> Path r -> Path r #

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

Defined in Ipe.Reader

(Coordinate r, Fractional r, Eq r) => IpeReadText (Path r) Source # 
Instance details

Defined in Ipe.Reader

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

Defined in Ipe.Writer

Methods

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

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

Defined in Ipe.Writer

type Dimension (Path r) Source # 
Instance details

Defined in Ipe.Path

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

Defined in Ipe.Path

type NumType (Path r) = r

pathSegments :: forall r r. Iso (Path r) (Path r) (LSeq 1 (PathSegment r)) (LSeq 1 (PathSegment r)) Source #

data PathSegment r Source #

Paths

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

Instances

Instances details
Functor PathSegment Source # 
Instance details

Defined in Ipe.Path

Methods

fmap :: (a -> b) -> PathSegment a -> PathSegment b #

(<$) :: a -> PathSegment b -> PathSegment a #

Foldable PathSegment Source # 
Instance details

Defined in Ipe.Path

Methods

fold :: Monoid m => PathSegment m -> m #

foldMap :: Monoid m => (a -> m) -> PathSegment a -> m #

foldMap' :: Monoid m => (a -> m) -> PathSegment a -> m #

foldr :: (a -> b -> b) -> b -> PathSegment a -> b #

foldr' :: (a -> b -> b) -> b -> PathSegment a -> b #

foldl :: (b -> a -> b) -> b -> PathSegment a -> b #

foldl' :: (b -> a -> b) -> b -> PathSegment a -> b #

foldr1 :: (a -> a -> a) -> PathSegment a -> a #

foldl1 :: (a -> a -> a) -> PathSegment a -> a #

toList :: PathSegment a -> [a] #

null :: PathSegment a -> Bool #

length :: PathSegment a -> Int #

elem :: Eq a => a -> PathSegment a -> Bool #

maximum :: Ord a => PathSegment a -> a #

minimum :: Ord a => PathSegment a -> a #

sum :: Num a => PathSegment a -> a #

product :: Num a => PathSegment a -> a #

Traversable PathSegment Source # 
Instance details

Defined in Ipe.Path

Methods

traverse :: Applicative f => (a -> f b) -> PathSegment a -> f (PathSegment b) #

sequenceA :: Applicative f => PathSegment (f a) -> f (PathSegment a) #

mapM :: Monad m => (a -> m b) -> PathSegment a -> m (PathSegment b) #

sequence :: Monad m => PathSegment (m a) -> m (PathSegment a) #

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

Defined in Ipe.Path

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

Defined in Ipe.Path

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

Defined in Ipe.Path

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

Defined in Ipe.Reader

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

Defined in Ipe.Writer

type Dimension (PathSegment r) Source # 
Instance details

Defined in Ipe.Path

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

Defined in Ipe.Path

type NumType (PathSegment r) = r

newtype Group r Source #

Groups and Objects

Group Attributes

A group is essentially a list of IpeObjects.

Constructors

Group [IpeObject r] 

Instances

Instances details
Functor Group Source # 
Instance details

Defined in Ipe.Content

Methods

fmap :: (a -> b) -> Group a -> Group b #

(<$) :: a -> Group b -> Group a #

Foldable Group Source # 
Instance details

Defined in Ipe.Content

Methods

fold :: Monoid m => Group m -> m #

foldMap :: Monoid m => (a -> m) -> Group a -> m #

foldMap' :: Monoid m => (a -> m) -> Group a -> m #

foldr :: (a -> b -> b) -> b -> Group a -> b #

foldr' :: (a -> b -> b) -> b -> Group a -> b #

foldl :: (b -> a -> b) -> b -> Group a -> b #

foldl' :: (b -> a -> b) -> b -> Group a -> b #

foldr1 :: (a -> a -> a) -> Group a -> a #

foldl1 :: (a -> a -> a) -> Group a -> a #

toList :: Group a -> [a] #

null :: Group a -> Bool #

length :: Group a -> Int #

elem :: Eq a => a -> Group a -> Bool #

maximum :: Ord a => Group a -> a #

minimum :: Ord a => Group a -> a #

sum :: Num a => Group a -> a #

product :: Num a => Group a -> a #

Traversable Group Source # 
Instance details

Defined in Ipe.Content

Methods

traverse :: Applicative f => (a -> f b) -> Group a -> f (Group b) #

sequenceA :: Applicative f => Group (f a) -> f (Group a) #

mapM :: Monad m => (a -> m b) -> Group a -> m (Group b) #

sequence :: Monad m => Group (m a) -> m (Group a) #

ToObject Group Source # 
Instance details

Defined in Ipe.Content

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

Defined in Ipe.Content

Methods

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

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

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

Defined in Ipe.Content

Methods

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

show :: Group r -> String #

showList :: [Group r] -> ShowS #

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

Defined in Ipe.Content

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

Defined in Ipe.Reader

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

Defined in Ipe.Writer

type Dimension (Group r) Source # 
Instance details

Defined in Ipe.Content

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

Defined in Ipe.Content

type NumType (Group r) = r

data IpeObject r Source #

Instances

Instances details
Functor IpeObject Source # 
Instance details

Defined in Ipe.Content

Methods

fmap :: (a -> b) -> IpeObject a -> IpeObject b #

(<$) :: a -> IpeObject b -> IpeObject a #

Foldable IpeObject Source # 
Instance details

Defined in Ipe.Content

Methods

fold :: Monoid m => IpeObject m -> m #

foldMap :: Monoid m => (a -> m) -> IpeObject a -> m #

foldMap' :: Monoid m => (a -> m) -> IpeObject a -> m #

foldr :: (a -> b -> b) -> b -> IpeObject a -> b #

foldr' :: (a -> b -> b) -> b -> IpeObject a -> b #

foldl :: (b -> a -> b) -> b -> IpeObject a -> b #

foldl' :: (b -> a -> b) -> b -> IpeObject a -> b #

foldr1 :: (a -> a -> a) -> IpeObject a -> a #

foldl1 :: (a -> a -> a) -> IpeObject a -> a #

toList :: IpeObject a -> [a] #

null :: IpeObject a -> Bool #

length :: IpeObject a -> Int #

elem :: Eq a => a -> IpeObject a -> Bool #

maximum :: Ord a => IpeObject a -> a #

minimum :: Ord a => IpeObject a -> a #

sum :: Num a => IpeObject a -> a #

product :: Num a => IpeObject a -> a #

Traversable IpeObject Source # 
Instance details

Defined in Ipe.Content

Methods

traverse :: Applicative f => (a -> f b) -> IpeObject a -> f (IpeObject b) #

sequenceA :: Applicative f => IpeObject (f a) -> f (IpeObject a) #

mapM :: Monad m => (a -> m b) -> IpeObject a -> m (IpeObject b) #

sequence :: Monad m => IpeObject (m a) -> m (IpeObject a) #

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

Defined in Ipe.Content

Methods

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

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

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

Defined in Ipe.Content

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

Defined in Ipe.Content

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

Defined in Ipe.Reader

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

Defined in Ipe.Writer

type Dimension (IpeObject r) Source # 
Instance details

Defined in Ipe.Content

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

Defined in Ipe.Content

type NumType (IpeObject r) = r

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

An IpeObject' is essentially the oject ogether with its attributes

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

Shorthand for constructing ipeObjects

class ToObject i where Source #

Instances

Instances details
ToObject Path Source # 
Instance details

Defined in Ipe.Content

ToObject Image Source # 
Instance details

Defined in Ipe.Content

ToObject IpeSymbol Source # 
Instance details

Defined in Ipe.Content

ToObject MiniPage Source # 
Instance details

Defined in Ipe.Content

ToObject TextLabel Source # 
Instance details

Defined in Ipe.Content

ToObject Group Source # 
Instance details

Defined in Ipe.Content

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

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

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

data AttrMapSym1 a6989586621679197913 a6989586621679197914 Source #

Instances

Instances details
SuppressUnusedWarnings (AttrMapSym1 a6989586621679197913 :: TyFun AttributeUniverse Type -> Type) Source # 
Instance details

Defined in Ipe.Content

type Apply (AttrMapSym1 a6989586621679197913 :: TyFun AttributeUniverse Type -> Type) (a6989586621679197914 :: AttributeUniverse) Source # 
Instance details

Defined in Ipe.Content

type Apply (AttrMapSym1 a6989586621679197913 :: TyFun AttributeUniverse Type -> Type) (a6989586621679197914 :: AttributeUniverse)

traverseIpeAttrs :: (Applicative f, AllConstrained TraverseIpeAttr (AttributesOf g)) => proxy g -> (r -> f s) -> IpeAttributes g r -> f (IpeAttributes g s) Source #

traverse for ipe attributes

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

collect all non-group objects