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

Ipe

Description

Reexports the functionality for reading and writing Ipe files.

Synopsis

Ipe Files

data IpeFile r Source #

A complete ipe file

Instances

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

Defined in Ipe.Types

Methods

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

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

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

Defined in Ipe.Types

Methods

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

show :: IpeFile r -> String #

showList :: [IpeFile r] -> ShowS #

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

Defined in Ipe.Reader

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

Defined in Ipe.Writer

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

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

ipeFile :: NonEmpty (IpePage r) -> IpeFile r Source #

Convenience constructor for creating an ipe file without preamble and with the default stylesheet.

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

Reading Ipe files

readIpeFile :: (Coordinate r, Eq r) => FilePath -> IO (Either ConversionError (IpeFile r)) Source #

Given a file path, tries to read an ipe file.

This function applies all matrices to objects.

readSinglePageFile :: (Coordinate r, Eq r) => FilePath -> IO (Either ConversionError (IpePage r)) Source #

Since most Ipe file contain only one page, we provide a shortcut for that as well.

This function applies all matrices, and it makes sure there is at least one layer and view in the page.

readSinglePageFileThrow :: (Coordinate r, Eq r) => FilePath -> IO (IpePage r) Source #

Tries to read a single page file, throws an error when this fails. See readSinglePageFile for further details.

readRawIpeFile :: (Coordinate r, Eq r) => FilePath -> IO (Either ConversionError (IpeFile r)) Source #

Given a file path, tries to read an ipe file

Reading all Geometries from a single page ipe file

readAll :: forall g r. (HasDefaultFromIpe g, r ~ NumType g) => IpePage r -> [g :+ IpeAttributes (DefaultFromIpe g) r] Source #

Read all g's from some ipe page(s).

readAllFrom :: forall g r. (HasDefaultFromIpe g, r ~ NumType g, Coordinate r, Eq r) => FilePath -> IO [g :+ IpeAttributes (DefaultFromIpe g) r] Source #

Convenience function from reading all g's from an ipe file. If there is an error reading or parsing the file the error is "thrown away".

Writing ipe files

writeIpeFile :: IpeWriteText r => FilePath -> IpeFile r -> IO () Source #

Given a prism to convert something of type g into an ipe file, a file path, and a g. Convert the geometry and write it to file.

Write an IpeFiele to file.

writeIpeFile' :: IpeWrite t => t -> FilePath -> IO () Source #

Convert to ipe XML and write the output to a file.

writeIpePage :: IpeWriteText r => FilePath -> IpePage r -> IO () Source #

Creates a single page ipe file with the given page

toIpeXML :: IpeWrite t => t -> Maybe ByteString Source #

Convert to Ipe xml

printAsIpeSelection :: IpeWrite t => t -> IO () Source #

Convert the input to ipeXml, and prints it to standard out in such a way that the copied text can be pasted into ipe as a geometry object.

toIpeSelectionXML :: IpeWrite t => t -> Maybe ByteString Source #

Convert input into an ipe selection.

Ipe Pages

data IpePage r Source #

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

Constructors

IpePage [LayerName] [View] [IpeObject r] 

Instances

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

Defined in Ipe.Types

Methods

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

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

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

Defined in Ipe.Types

Methods

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

show :: IpePage r -> String #

showList :: [IpePage r] -> ShowS #

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

Defined in Ipe.Reader

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

Defined in Ipe.Writer

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

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

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

emptyPage :: IpePage r Source #

Creates an empty page with one layer and view.

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

Creates a simple page with a single view.

onLayer :: LayerName -> Getting (Endo [IpeObject r]) [IpeObject r] (IpeObject r) Source #

This allows you to filter the objects on some layer.

>>> let page = IpePage [] [] []
>>> page^..content.onLayer "myLayer"
[]

contentInView :: Word -> Getter (IpePage r) [IpeObject r] Source #

Gets all objects that are visible in the given view.

Note that views are indexed starting from 0. If the page does not have any explicit view definitions, this function returns an empty list.

>>> let page = IpePage [] [] []
>>> page^.contentInView 0
[]

withDefaults :: IpePage r -> IpePage r Source #

Makes sure that the page has at least one layer and at least one view, essentially matching the behaviour of ipe. In particular,

  • if the page does not have any layers, it creates a layer named "alpha", and
  • if the page does not have any views, it creates a view in which all layers are visible.

Content: Ipe Objects

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

Specific Ipe-Objects

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

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

Attributes

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

Layers and Views

newtype LayerName Source #

Defines an Layer in Ipe.

Constructors

LayerName Text 

Instances

Instances details
Eq LayerName Source # 
Instance details

Defined in Ipe.Layer

Ord LayerName Source # 
Instance details

Defined in Ipe.Layer

Read LayerName Source # 
Instance details

Defined in Ipe.Layer

Show LayerName Source # 
Instance details

Defined in Ipe.Layer

IsString LayerName Source # 
Instance details

Defined in Ipe.Layer

IpeRead LayerName Source # 
Instance details

Defined in Ipe.Reader

IpeReadText LayerName Source # 
Instance details

Defined in Ipe.Reader

IpeWrite LayerName Source # 
Instance details

Defined in Ipe.Writer

IpeWriteText LayerName Source # 
Instance details

Defined in Ipe.Writer

data View Source #

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

Constructors

View [LayerName] LayerName 

Instances

Instances details
Eq View Source # 
Instance details

Defined in Ipe.Types

Methods

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

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

Ord View Source # 
Instance details

Defined in 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 Ipe.Types

Methods

showsPrec :: Int -> View -> ShowS #

show :: View -> String #

showList :: [View] -> ShowS #

IpeRead View Source # 
Instance details

Defined in Ipe.Reader

IpeWrite View Source # 
Instance details

Defined in Ipe.Writer

Ipe Syles and Preamble

data IpeStyle Source #

for now we pretty much ignore these

Constructors

IpeStyle (Maybe Text) (Node Text Text) 

Instances

Instances details
Eq IpeStyle Source # 
Instance details

Defined in Ipe.Types

Show IpeStyle Source # 
Instance details

Defined in Ipe.Types

IpeRead IpeStyle Source # 
Instance details

Defined in Ipe.Reader

IpeWrite IpeStyle Source # 
Instance details

Defined in Ipe.Writer

readIpeStylesheet :: FilePath -> IO (Either ConversionError IpeStyle) Source #

Reads an Ipe stylesheet from Disk.

addStyleSheetFrom :: FilePath -> IpeFile r -> IO (IpeFile r) Source #

Given a path to a stylesheet, add it to the ipe file with the highest priority. Throws an error when this fails.

data IpePreamble Source #

The maybe string is the encoding

Constructors

IpePreamble (Maybe Text) Text 

Reading Geometries *From* Ipe

class IpeRead t where Source #

Reading an ipe lement from Xml

Instances

Instances details
IpeRead LayerName Source # 
Instance details

Defined in Ipe.Reader

IpeRead View Source # 
Instance details

Defined in Ipe.Reader

IpeRead IpeStyle Source # 
Instance details

Defined in Ipe.Reader

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

Defined in Ipe.Reader

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

Defined in Ipe.Reader

Coordinate r => IpeRead (IpeSymbol r) Source #

Ipe read instances

Instance details

Defined in Ipe.Reader

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

Defined in Ipe.Reader

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

Defined in Ipe.Reader

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

Defined in Ipe.Reader

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

Defined in Ipe.Reader

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

Defined in Ipe.Reader

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

Defined in Ipe.Reader

Converting *from* IpeObjects

_asPoint :: Prism' (IpeSymbol r) (Point 2 r) Source #

Extracts the point from a Symbol. When creating a symbol this creates a disk that supports a stroke color.

_asLineSegment :: Prism' (Path r) (LineSegment 2 () r) Source #

Try to convert a path into a line segment, fails if the path is not a line segment or a polyline with more than two points.

_asRectangle :: forall r. (Num r, Ord r) => Prism' (Path r) (Rectangle () r) Source #

Tries to convert a path into a rectangle.

_asTriangle :: Prism' (Path r) (Triangle 2 () r) Source #

Convert to a triangle

_asPolyLine :: Prism' (Path r) (PolyLine 2 () r) Source #

Convert to a polyline. Ignores all non-polyline parts

>>> testPath ^? _asPolyLine
Just (PolyLine {_points = LSeq (fromList [Point2 [0,0] :+ (),Point2 [10,10] :+ (),Point2 [200,100] :+ ()])})

_asSimplePolygon :: Prism' (Path r) (Polygon Simple () r) Source #

Convert to a simple polygon

_asMultiPolygon :: Prism' (Path r) (MultiPolygon () r) Source #

Convert to a multipolygon

Dealing with Attributes

_withAttrs :: Prism' (IpeObject r) (i r :+ IpeAttributes i r) -> Prism' (i r) g -> Prism' (IpeObject r) (g :+ IpeAttributes i r) Source #

Use the first prism to select the ipe object to depicle with, and the second how to select the geometry object from there on. Then we can select the geometry object, directly with its attributes here.

>>> testObject ^? _withAttrs _IpePath _asPolyLine
Just (PolyLine {_points = LSeq (fromList [Point2 [0,0] :+ (),Point2 [10,10] :+ (),Point2 [200,100] :+ ()])} :+ Attrs {NoAttr, NoAttr, NoAttr, NoAttr, Attr IpeColor (Named "red"), NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr, NoAttr})

Default readers

class HasDefaultFromIpe g where Source #

Associated Types

type DefaultFromIpe g :: * -> * Source #

Instances

Instances details
HasDefaultFromIpe (Ellipse r) Source # 
Instance details

Defined in Ipe.FromIpe

Associated Types

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

HasDefaultFromIpe (SimplePolygon () r) Source # 
Instance details

Defined in Ipe.FromIpe

Associated Types

type DefaultFromIpe (SimplePolygon () r) :: Type -> Type Source #

HasDefaultFromIpe (MultiPolygon () r) Source # 
Instance details

Defined in Ipe.FromIpe

Associated Types

type DefaultFromIpe (MultiPolygon () r) :: Type -> Type Source #

(Floating r, Eq r) => HasDefaultFromIpe (Disk () r) Source # 
Instance details

Defined in Ipe.FromIpe

Associated Types

type DefaultFromIpe (Disk () r) :: Type -> Type Source #

Methods

defaultFromIpe :: r0 ~ NumType (Disk () r) => Prism' (IpeObject r0) (Disk () r :+ IpeAttributes (DefaultFromIpe (Disk () r)) r0) Source #

(Floating r, Eq r) => HasDefaultFromIpe (Circle () r) Source # 
Instance details

Defined in Ipe.FromIpe

Associated Types

type DefaultFromIpe (Circle () r) :: Type -> Type Source #

Methods

defaultFromIpe :: r0 ~ NumType (Circle () r) => Prism' (IpeObject r0) (Circle () r :+ IpeAttributes (DefaultFromIpe (Circle () r)) r0) Source #

HasDefaultFromIpe (Point 2 r) Source # 
Instance details

Defined in Ipe.FromIpe

Associated Types

type DefaultFromIpe (Point 2 r) :: Type -> Type Source #

HasDefaultFromIpe (PolyLine 2 () r) Source # 
Instance details

Defined in Ipe.FromIpe

Associated Types

type DefaultFromIpe (PolyLine 2 () r) :: Type -> Type Source #

Methods

defaultFromIpe :: r0 ~ NumType (PolyLine 2 () r) => Prism' (IpeObject r0) (PolyLine 2 () r :+ IpeAttributes (DefaultFromIpe (PolyLine 2 () r)) r0) Source #

HasDefaultFromIpe (LineSegment 2 () r) Source # 
Instance details

Defined in Ipe.FromIpe

Associated Types

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

Converting *to* IpeObjects

IpeWrite

class IpeWrite t where Source #

Types that correspond to an XML Element. All instances should produce an Element. If the type should produce a Node with the Text constructor, use the IpeWriteText typeclass instead.

Methods

ipeWrite :: t -> Maybe (Node Text Text) Source #

Instances

Instances details
IpeWrite () Source # 
Instance details

Defined in Ipe.Writer

Methods

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

IpeWrite LayerName Source # 
Instance details

Defined in Ipe.Writer

IpeWrite View Source # 
Instance details

Defined in Ipe.Writer

IpeWrite IpeStyle Source # 
Instance details

Defined in Ipe.Writer

IpeWrite IpePreamble Source # 
Instance details

Defined in Ipe.Writer

IpeWrite t => IpeWrite [t] Source # 
Instance details

Defined in Ipe.Writer

Methods

ipeWrite :: [t] -> Maybe (Node Text Text) Source #

IpeWrite t => IpeWrite (NonEmpty t) Source # 
Instance details

Defined in Ipe.Writer

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

Defined in Ipe.Writer

Methods

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

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

Defined in Ipe.Writer

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

Defined in Ipe.Writer

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

Defined in Ipe.Writer

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

Defined in Ipe.Writer

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

Defined in Ipe.Writer

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

Defined in Ipe.Writer

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

Defined in Ipe.Writer

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

Defined in Ipe.Writer

(IpeWrite l, IpeWrite r) => IpeWrite (Either l r) Source # 
Instance details

Defined in Ipe.Writer

Methods

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

(AllConstrained IpeAttrName rs, RecordToList rs, RMap rs, ReifyConstraint IpeWriteText (Attr f) rs, RecAll (Attr f) rs IpeWriteText, IpeWrite g) => IpeWrite (g :+ Attributes f rs) Source # 
Instance details

Defined in Ipe.Writer

Methods

ipeWrite :: (g :+ Attributes f rs) -> Maybe (Node Text Text) Source #

(IpeWriteText r, IpeWrite p) => IpeWrite (PolyLine 2 p r) Source # 
Instance details

Defined in Ipe.Writer

Methods

ipeWrite :: PolyLine 2 p r -> Maybe (Node Text Text) Source #

IpeWriteText r => IpeWrite (LineSegment 2 p r) Source # 
Instance details

Defined in Ipe.Writer

class IpeWriteText t where Source #

For types that can produce a text value

Methods

ipeWriteText :: t -> Maybe Text Source #

Instances

Instances details
IpeWriteText Double Source # 
Instance details

Defined in Ipe.Writer

IpeWriteText Float Source # 
Instance details

Defined in Ipe.Writer

IpeWriteText Int Source # 
Instance details

Defined in Ipe.Writer

IpeWriteText Integer Source # 
Instance details

Defined in Ipe.Writer

IpeWriteText () Source # 
Instance details

Defined in Ipe.Writer

Methods

ipeWriteText :: () -> Maybe Text Source #

IpeWriteText String Source # 
Instance details

Defined in Ipe.Writer

IpeWriteText Text Source # 
Instance details

Defined in Ipe.Writer

IpeWriteText LayerName Source # 
Instance details

Defined in Ipe.Writer

IpeWriteText FillType Source # 
Instance details

Defined in Ipe.Writer

IpeWriteText TransformationTypes Source # 
Instance details

Defined in Ipe.Writer

IpeWriteText PinType Source # 
Instance details

Defined in Ipe.Writer

Integral a => IpeWriteText (Ratio a) Source #

This instance converts the ratio to a Pico, and then displays that.

Instance details

Defined in Ipe.Writer

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

Defined in Ipe.Writer

IpeWriteText (RealNumber p) Source # 
Instance details

Defined in Ipe.Writer

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

Defined in Ipe.Writer

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

Defined in Ipe.Writer

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

Defined in Ipe.Writer

IpeWriteText v => IpeWriteText (IpeValue v) Source # 
Instance details

Defined in Ipe.Writer

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

Defined in Ipe.Writer

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

Defined in Ipe.Writer

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

Defined in Ipe.Writer

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

Defined in Ipe.Writer

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

Defined in Ipe.Writer

(IpeWriteText l, IpeWriteText r) => IpeWriteText (Either l r) Source # 
Instance details

Defined in Ipe.Writer

HasResolution p => IpeWriteText (Fixed p) Source # 
Instance details

Defined in Ipe.Writer

IpeWriteText r => IpeWriteText (Point 2 r) Source # 
Instance details

Defined in Ipe.Writer

Methods

ipeWriteText :: Point 2 r -> Maybe Text Source #

IpeWriteText r => IpeWriteText (BezierSpline 3 2 r) Source # 
Instance details

Defined in Ipe.Writer

IpeWriteText r => IpeWriteText (Polygon t () r) Source # 
Instance details

Defined in Ipe.Writer

Methods

ipeWriteText :: Polygon t () r -> Maybe Text Source #

IpeWriteText r => IpeWriteText (PolyLine 2 () r) Source # 
Instance details

Defined in Ipe.Writer

Methods

ipeWriteText :: PolyLine 2 () r -> Maybe Text Source #

IpeWriteText r => IpeWriteText (Matrix 3 3 r) Source # 
Instance details

Defined in Ipe.Writer

Methods

ipeWriteText :: Matrix 3 3 r -> Maybe Text Source #

IpeWriteText (Apply f at) => IpeWriteText (Attr f at) Source # 
Instance details

Defined in Ipe.Writer

Methods

ipeWriteText :: Attr f at -> Maybe Text Source #

IpeOut

module Ipe.IpeOut

Batch reexports

module Ipe.Types

module Ipe.Value

newtype IpeColor r Source #

Defines a color in Ipe. Colors are either RGB Values or Named values.

Constructors

IpeColor (IpeValue (RGB r)) 

Instances

Instances details
Functor IpeColor Source # 
Instance details

Defined in Ipe.Color

Methods

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

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

Foldable IpeColor Source # 
Instance details

Defined in Ipe.Color

Methods

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

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

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

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

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

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

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

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

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

toList :: IpeColor a -> [a] #

null :: IpeColor a -> Bool #

length :: IpeColor a -> Int #

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

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

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

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

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

Traversable IpeColor Source # 
Instance details

Defined in Ipe.Color

Methods

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

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

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

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

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

Defined in Ipe.Color

Methods

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

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

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

Defined in Ipe.Color

Methods

compare :: IpeColor r -> IpeColor r -> Ordering #

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

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

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

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

max :: IpeColor r -> IpeColor r -> IpeColor r #

min :: IpeColor r -> IpeColor r -> IpeColor r #

Read r => Read (IpeColor r) Source # 
Instance details

Defined in Ipe.Color

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

Defined in Ipe.Color

Methods

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

show :: IpeColor r -> String #

showList :: [IpeColor r] -> ShowS #

Coordinate r => IpeReadText (IpeColor r) Source # 
Instance details

Defined in Ipe.Reader

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

Defined in Ipe.Writer

named :: Text -> IpeColor r Source #

Creates a named color