hgeometry-1.0.0.0: Geometric Algorithms, Data structures, and Data types.
Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellSafe-Inferred
LanguageGHC2021

Ipe.Attributes

Description

Possible Attributes we can assign to items in an Ipe file

Synopsis

Documentation

data AttributeUniverse Source #

The possible Attributes supported in Ipe. To use these attributes, you'll likely need their Singletons's version which is Prefixed by an S. E.g. the Fill attribute is represented by a singleton 'SFill :: Sing Fill'.

Instances

Instances details
Read AttributeUniverse Source # 
Instance details

Defined in Ipe.Attributes

Show AttributeUniverse Source # 
Instance details

Defined in Ipe.Attributes

Eq AttributeUniverse Source # 
Instance details

Defined in Ipe.Attributes

SingKind AttributeUniverse Source # 
Instance details

Defined in Ipe.Attributes

Associated Types

type Demote AttributeUniverse = (r :: Type) Source #

SingI 'Arrow Source # 
Instance details

Defined in Ipe.Attributes

Methods

sing :: Sing 'Arrow Source #

SingI 'Clip Source # 
Instance details

Defined in Ipe.Attributes

Methods

sing :: Sing 'Clip Source #

SingI 'Dash Source # 
Instance details

Defined in Ipe.Attributes

Methods

sing :: Sing 'Dash Source #

SingI 'Depth Source # 
Instance details

Defined in Ipe.Attributes

Methods

sing :: Sing 'Depth Source #

SingI 'Fill Source # 
Instance details

Defined in Ipe.Attributes

Methods

sing :: Sing 'Fill Source #

SingI 'FillRule Source # 
Instance details

Defined in Ipe.Attributes

SingI 'Gradient Source # 
Instance details

Defined in Ipe.Attributes

SingI 'HAlign Source # 
Instance details

Defined in Ipe.Attributes

Methods

sing :: Sing 'HAlign Source #

SingI 'Height Source # 
Instance details

Defined in Ipe.Attributes

Methods

sing :: Sing 'Height Source #

SingI 'Layer Source # 
Instance details

Defined in Ipe.Attributes

Methods

sing :: Sing 'Layer Source #

SingI 'LineCap Source # 
Instance details

Defined in Ipe.Attributes

Methods

sing :: Sing 'LineCap Source #

SingI 'LineJoin Source # 
Instance details

Defined in Ipe.Attributes

SingI 'Matrix Source # 
Instance details

Defined in Ipe.Attributes

Methods

sing :: Sing 'Matrix Source #

SingI 'Opacity Source # 
Instance details

Defined in Ipe.Attributes

Methods

sing :: Sing 'Opacity Source #

SingI 'Pen Source # 
Instance details

Defined in Ipe.Attributes

Methods

sing :: Sing 'Pen Source #

SingI 'Pin Source # 
Instance details

Defined in Ipe.Attributes

Methods

sing :: Sing 'Pin Source #

SingI 'RArrow Source # 
Instance details

Defined in Ipe.Attributes

Methods

sing :: Sing 'RArrow Source #

SingI 'Size Source # 
Instance details

Defined in Ipe.Attributes

Methods

sing :: Sing 'Size Source #

SingI 'Stroke Source # 
Instance details

Defined in Ipe.Attributes

Methods

sing :: Sing 'Stroke Source #

SingI 'StrokeOpacity Source # 
Instance details

Defined in Ipe.Attributes

SingI 'Style Source # 
Instance details

Defined in Ipe.Attributes

Methods

sing :: Sing 'Style Source #

SingI 'Tiling Source # 
Instance details

Defined in Ipe.Attributes

Methods

sing :: Sing 'Tiling Source #

SingI 'Transformations Source # 
Instance details

Defined in Ipe.Attributes

SingI 'VAlign Source # 
Instance details

Defined in Ipe.Attributes

Methods

sing :: Sing 'VAlign Source #

SingI 'Width Source # 
Instance details

Defined in Ipe.Attributes

Methods

sing :: Sing 'Width 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 #

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

Defined in Ipe.Content

type Demote AttributeUniverse Source # 
Instance details

Defined in Ipe.Attributes

type Sing Source # 
Instance details

Defined in Ipe.Attributes

type Apply (AttrMapSym1 a6989586621679247788 :: TyFun AttributeUniverse Type -> Type) (a6989586621679247789 :: AttributeUniverse) Source # 
Instance details

Defined in Ipe.Content

type Apply (AttrMapSym1 a6989586621679247788 :: TyFun AttributeUniverse Type -> Type) (a6989586621679247789 :: AttributeUniverse) = AttrMap a6989586621679247788 a6989586621679247789

type family LayerSym0 :: AttributeUniverse where ... Source #

Equations

LayerSym0 = 'Layer 

type family MatrixSym0 :: AttributeUniverse where ... Source #

Equations

MatrixSym0 = 'Matrix 

type family PinSym0 :: AttributeUniverse where ... Source #

Equations

PinSym0 = 'Pin 

type family StrokeSym0 :: AttributeUniverse where ... Source #

Equations

StrokeSym0 = 'Stroke 

type family FillSym0 :: AttributeUniverse where ... Source #

Equations

FillSym0 = 'Fill 

type family PenSym0 :: AttributeUniverse where ... Source #

Equations

PenSym0 = 'Pen 

type family SizeSym0 :: AttributeUniverse where ... Source #

Equations

SizeSym0 = 'Size 

type family DashSym0 :: AttributeUniverse where ... Source #

Equations

DashSym0 = 'Dash 

type family LineCapSym0 :: AttributeUniverse where ... Source #

Equations

LineCapSym0 = 'LineCap 

type family LineJoinSym0 :: AttributeUniverse where ... Source #

Equations

LineJoinSym0 = 'LineJoin 

type family FillRuleSym0 :: AttributeUniverse where ... Source #

Equations

FillRuleSym0 = 'FillRule 

type family ArrowSym0 :: AttributeUniverse where ... Source #

Equations

ArrowSym0 = 'Arrow 

type family RArrowSym0 :: AttributeUniverse where ... Source #

Equations

RArrowSym0 = 'RArrow 

type family OpacitySym0 :: AttributeUniverse where ... Source #

Equations

OpacitySym0 = 'Opacity 

type family TilingSym0 :: AttributeUniverse where ... Source #

Equations

TilingSym0 = 'Tiling 

type family GradientSym0 :: AttributeUniverse where ... Source #

Equations

GradientSym0 = 'Gradient 

type family WidthSym0 :: AttributeUniverse where ... Source #

Equations

WidthSym0 = 'Width 

type family HeightSym0 :: AttributeUniverse where ... Source #

Equations

HeightSym0 = 'Height 

type family DepthSym0 :: AttributeUniverse where ... Source #

Equations

DepthSym0 = 'Depth 

type family VAlignSym0 :: AttributeUniverse where ... Source #

Equations

VAlignSym0 = 'VAlign 

type family HAlignSym0 :: AttributeUniverse where ... Source #

Equations

HAlignSym0 = 'HAlign 

type family StyleSym0 :: AttributeUniverse where ... Source #

Equations

StyleSym0 = 'Style 

type family ClipSym0 :: AttributeUniverse where ... Source #

Equations

ClipSym0 = 'Clip 

data SAttributeUniverse :: AttributeUniverse -> Type where Source #

Constructors

SLayer :: SAttributeUniverse ('Layer :: AttributeUniverse) 
SMatrix :: SAttributeUniverse ('Matrix :: AttributeUniverse) 
SPin :: SAttributeUniverse ('Pin :: AttributeUniverse) 
STransformations :: SAttributeUniverse ('Transformations :: AttributeUniverse) 
SStroke :: SAttributeUniverse ('Stroke :: AttributeUniverse) 
SFill :: SAttributeUniverse ('Fill :: AttributeUniverse) 
SPen :: SAttributeUniverse ('Pen :: AttributeUniverse) 
SSize :: SAttributeUniverse ('Size :: AttributeUniverse) 
SDash :: SAttributeUniverse ('Dash :: AttributeUniverse) 
SLineCap :: SAttributeUniverse ('LineCap :: AttributeUniverse) 
SLineJoin :: SAttributeUniverse ('LineJoin :: AttributeUniverse) 
SFillRule :: SAttributeUniverse ('FillRule :: AttributeUniverse) 
SArrow :: SAttributeUniverse ('Arrow :: AttributeUniverse) 
SRArrow :: SAttributeUniverse ('RArrow :: AttributeUniverse) 
SStrokeOpacity :: SAttributeUniverse ('StrokeOpacity :: AttributeUniverse) 
SOpacity :: SAttributeUniverse ('Opacity :: AttributeUniverse) 
STiling :: SAttributeUniverse ('Tiling :: AttributeUniverse) 
SGradient :: SAttributeUniverse ('Gradient :: AttributeUniverse) 
SWidth :: SAttributeUniverse ('Width :: AttributeUniverse) 
SHeight :: SAttributeUniverse ('Height :: AttributeUniverse) 
SDepth :: SAttributeUniverse ('Depth :: AttributeUniverse) 
SVAlign :: SAttributeUniverse ('VAlign :: AttributeUniverse) 
SHAlign :: SAttributeUniverse ('HAlign :: AttributeUniverse) 
SStyle :: SAttributeUniverse ('Style :: AttributeUniverse) 
SClip :: SAttributeUniverse ('Clip :: AttributeUniverse) 

type CommonAttributes = [Layer, Matrix, Pin, Transformations] Source #

IpeObjects may have attributes. Essentially attributes are (key,value) pairs. The key is some name. Which attributes an object can have depends on the type of the object. However, all ipe objects support the Common Attributes

type TextAttributes = CommonAttributes ++ [Stroke, Size, Width, Height, Depth, VAlign, HAlign, Style, Opacity] Source #

All attributes applicable to Text (TextLabels and Minipages)

type TextLabelAttributes = TextAttributes Source #

All attributes applicable to TextLabels

type MiniPageAttributes = TextAttributes Source #

All attributes applicable to Minipages

type ImageAttributes = CommonAttributes Source #

All attributes applicable to Images

type SymbolAttributes = CommonAttributes ++ [Stroke, Fill, Pen, Size] Source #

All attributes applicable to Symbols/Marks

type GroupAttributes = CommonAttributes ++ '['Clip] Source #

All attributes applicable to Groups

A single attribute Attr

newtype Attr (f :: TyFun u Type -> Type) (label :: u) Source #

Attr implements the mapping from labels to types as specified by the (symbol representing) the type family f

Constructors

GAttr 

Fields

Instances

Instances details
Monoid (Attr f l) Source # 
Instance details

Defined in Ipe.Attributes

Methods

mempty :: Attr f l #

mappend :: Attr f l -> Attr f l -> Attr f l #

mconcat :: [Attr f l] -> Attr f l #

Semigroup (Attr f l) Source #

Give pref. to the *RIGHT*

Instance details

Defined in Ipe.Attributes

Methods

(<>) :: Attr f l -> Attr f l -> Attr f l #

sconcat :: NonEmpty (Attr f l) -> Attr f l #

stimes :: Integral b => b -> Attr f l -> Attr f l #

Read (Apply f label) => Read (Attr f label) Source # 
Instance details

Defined in Ipe.Attributes

Methods

readsPrec :: Int -> ReadS (Attr f label) #

readList :: ReadS [Attr f label] #

readPrec :: ReadPrec (Attr f label) #

readListPrec :: ReadPrec [Attr f label] #

Show (Apply f label) => Show (Attr f label) Source # 
Instance details

Defined in Ipe.Attributes

Methods

showsPrec :: Int -> Attr f label -> ShowS #

show :: Attr f label -> String #

showList :: [Attr f label] -> ShowS #

Eq (Apply f label) => Eq (Attr f label) Source # 
Instance details

Defined in Ipe.Attributes

Methods

(==) :: Attr f label -> Attr f label -> Bool #

(/=) :: Attr f label -> Attr f label -> Bool #

Ord (Apply f label) => Ord (Attr f label) Source # 
Instance details

Defined in Ipe.Attributes

Methods

compare :: Attr f label -> Attr f label -> Ordering #

(<) :: Attr f label -> Attr f label -> Bool #

(<=) :: Attr f label -> Attr f label -> Bool #

(>) :: Attr f label -> Attr f label -> Bool #

(>=) :: Attr f label -> Attr f label -> Bool #

max :: Attr f label -> Attr f label -> Attr f label #

min :: Attr f label -> Attr f label -> Attr f label #

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

Defined in Ipe.Reader

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

Defined in Ipe.Writer

Methods

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

getAttr :: forall u (f :: TyFun u Type -> Type) (label :: u) u (f :: TyFun u Type -> Type) (label :: u). Iso (Attr (f :: TyFun u Type -> Type) (label :: u)) (Attr (f :: TyFun u Type -> Type) (label :: u)) (Maybe (Apply f label)) (Maybe (Apply f label)) Source #

pattern Attr :: Apply f label -> Attr f label Source #

Constructor for constructing an Attr given an actual value.

pattern NoAttr :: Attr f label Source #

An Attribute that is not set

traverseAttr :: Applicative h => (Apply f label -> h (Apply g label)) -> Attr f label -> h (Attr g label) Source #

Traverse an attribute.

pureAttr :: (Applicative h, Apply f a ~ Apply g a) => Attr f a -> h (Attr g a) Source #

Traverse for the situation where the type is not actually parameterized.

Attributes

newtype Attributes (f :: TyFun u Type -> Type) (ats :: [u]) Source #

A collection of Attributes.

Constructors

Attrs (Rec (Attr f) ats) 

Instances

Instances details
(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 #

RecApplicative ats => Monoid (Attributes f ats) Source # 
Instance details

Defined in Ipe.Attributes

Methods

mempty :: Attributes f ats #

mappend :: Attributes f ats -> Attributes f ats -> Attributes f ats #

mconcat :: [Attributes f ats] -> Attributes f ats #

Semigroup (Attributes f ats) Source # 
Instance details

Defined in Ipe.Attributes

Methods

(<>) :: Attributes f ats -> Attributes f ats -> Attributes f ats #

sconcat :: NonEmpty (Attributes f ats) -> Attributes f ats #

stimes :: Integral b => b -> Attributes f ats -> Attributes f ats #

(RMap ats, ReifyConstraint Show (Attr f) ats, RecordToList ats, RecAll (Attr f) ats Show) => Show (Attributes f ats) Source # 
Instance details

Defined in Ipe.Attributes

Methods

showsPrec :: Int -> Attributes f ats -> ShowS #

show :: Attributes f ats -> String #

showList :: [Attributes f ats] -> ShowS #

(ReifyConstraint Eq (Attr f) ats, RecordToList ats, RecAll (Attr f) ats Eq) => Eq (Attributes f ats) Source # 
Instance details

Defined in Ipe.Attributes

Methods

(==) :: Attributes f ats -> Attributes f ats -> Bool #

(/=) :: Attributes f ats -> Attributes f ats -> Bool #

unAttrs :: Lens (Attributes f ats) (Attributes f' ats') (Rec (Attr f) ats) (Rec (Attr f') ats') Source #

Get a vinyl Record with Attrs

traverseAttrs :: Applicative h => (forall label. Attr f label -> h (Attr g label)) -> Attributes f ats -> h (Attributes g ats) Source #

Traverse implementation for Attrs

zipRecsWith :: (forall a. f a -> g a -> h a) -> Rec f as -> Rec g as -> Rec h as Source #

Zip two Recs with the given function.

ixAttr :: forall at ats proxy f. at ats => proxy at -> Lens' (Attributes f ats) (Maybe (Apply f at)) Source #

Lens into a specific attribute, if it is set.

_Attr :: forall at ats proxy f. (at ats, RecApplicative ats) => proxy at -> Prism' (Attributes f ats) (Apply f at) Source #

Prism into a particular attribute.

lookupAttr :: at ats => proxy at -> Attributes f ats -> Maybe (Apply f at) Source #

Looks up a particular attribute.

setAttr :: forall proxy at ats f. at ats => proxy at -> Apply f at -> Attributes f ats -> Attributes f ats Source #

Sets a particular attribute

takeAttr :: forall proxy at ats f. at ats => proxy at -> Attributes f ats -> (Maybe (Apply f at), Attributes f ats) Source #

gets and removes the attribute from Attributes

unSetAttr :: forall proxy at ats f. at ats => proxy at -> Attributes f ats -> Attributes f ats Source #

unsets/Removes an attribute

attr :: (at ats, RecApplicative ats) => proxy at -> Apply f at -> Attributes f ats Source #

Creates a singleton attribute

Implementations for Common Attributes

data PinType Source #

Possible values for Pin

Constructors

No 
Yes 
Horizontal 
Vertical 

Instances

Instances details
Enum PinType Source # 
Instance details

Defined in Ipe.Attributes

Read PinType Source # 
Instance details

Defined in Ipe.Attributes

Show PinType Source # 
Instance details

Defined in Ipe.Attributes

Eq PinType Source # 
Instance details

Defined in Ipe.Attributes

Methods

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

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

IpeReadText PinType Source # 
Instance details

Defined in Ipe.Reader

IpeWriteText PinType Source # 
Instance details

Defined in Ipe.Writer

data TransformationTypes Source #

Possible values for Transformation

Constructors

Affine 
Rigid 
Translations 

Instances

Instances details
Enum TransformationTypes Source # 
Instance details

Defined in Ipe.Attributes

Read TransformationTypes Source # 
Instance details

Defined in Ipe.Attributes

Show TransformationTypes Source # 
Instance details

Defined in Ipe.Attributes

Eq TransformationTypes Source # 
Instance details

Defined in Ipe.Attributes

IpeReadText TransformationTypes Source # 
Instance details

Defined in Ipe.Reader

IpeWriteText TransformationTypes Source # 
Instance details

Defined in Ipe.Writer

Text Attributes

data HorizontalAlignment Source #

Instances

Instances details
Enum HorizontalAlignment Source # 
Instance details

Defined in Ipe.Attributes

Read HorizontalAlignment Source # 
Instance details

Defined in Ipe.Attributes

Show HorizontalAlignment Source # 
Instance details

Defined in Ipe.Attributes

Eq HorizontalAlignment Source # 
Instance details

Defined in Ipe.Attributes

Ord HorizontalAlignment Source # 
Instance details

Defined in Ipe.Attributes

IpeReadText HorizontalAlignment Source # 
Instance details

Defined in Ipe.Reader

IpeWriteText HorizontalAlignment Source # 
Instance details

Defined in Ipe.Writer

data VerticalAlignment Source #

Instances

Instances details
Enum VerticalAlignment Source # 
Instance details

Defined in Ipe.Attributes

Read VerticalAlignment Source # 
Instance details

Defined in Ipe.Attributes

Show VerticalAlignment Source # 
Instance details

Defined in Ipe.Attributes

Eq VerticalAlignment Source # 
Instance details

Defined in Ipe.Attributes

Ord VerticalAlignment Source # 
Instance details

Defined in Ipe.Attributes

IpeReadText VerticalAlignment Source # 
Instance details

Defined in Ipe.Reader

IpeWriteText VerticalAlignment Source # 
Instance details

Defined in Ipe.Writer

type TeXStyle = Text Source #

Should be a symbolic name.

type TextSizeUnit r = r Source #

size of text in points

Symbol Attributes

newtype IpeSize r Source #

The optional Attributes for a symbol data SymbolAttributeUniverse = SymbolStroke | SymbolFill | SymbolPen | Size deriving (Show,Eq)

Size

Constructors

IpeSize (IpeValue r) 

Instances

Instances details
Foldable IpeSize Source # 
Instance details

Defined in Ipe.Attributes

Methods

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

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

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

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

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

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

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

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

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

toList :: IpeSize a -> [a] #

null :: IpeSize a -> Bool #

length :: IpeSize a -> Int #

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

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

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

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

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

Traversable IpeSize Source # 
Instance details

Defined in Ipe.Attributes

Methods

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

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

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

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

Functor IpeSize Source # 
Instance details

Defined in Ipe.Attributes

Methods

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

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

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

Defined in Ipe.Attributes

Methods

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

show :: IpeSize r -> String #

showList :: [IpeSize r] -> ShowS #

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

Defined in Ipe.Attributes

Methods

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

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

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

Defined in Ipe.Attributes

Methods

compare :: IpeSize r -> IpeSize r -> Ordering #

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

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

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

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

max :: IpeSize r -> IpeSize r -> IpeSize r #

min :: IpeSize r -> IpeSize r -> IpeSize r #

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

Defined in Ipe.Reader

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

Defined in Ipe.Writer

newtype IpePen r Source #

Pen/Thickness

Constructors

IpePen (IpeValue r) 

Instances

Instances details
Foldable IpePen Source # 
Instance details

Defined in Ipe.Attributes

Methods

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

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

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

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

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

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

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

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

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

toList :: IpePen a -> [a] #

null :: IpePen a -> Bool #

length :: IpePen a -> Int #

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

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

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

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

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

Traversable IpePen Source # 
Instance details

Defined in Ipe.Attributes

Methods

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

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

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

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

Functor IpePen Source # 
Instance details

Defined in Ipe.Attributes

Methods

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

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

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

Defined in Ipe.Attributes

Methods

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

show :: IpePen r -> String #

showList :: [IpePen r] -> ShowS #

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

Defined in Ipe.Attributes

Methods

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

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

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

Defined in Ipe.Attributes

Methods

compare :: IpePen r -> IpePen r -> Ordering #

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

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

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

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

max :: IpePen r -> IpePen r -> IpePen r #

min :: IpePen r -> IpePen r -> IpePen r #

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

Defined in Ipe.Reader

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

Defined in Ipe.Writer

Path Attributes

data IpeDash r Source #

Possible values for Dash

Constructors

DashNamed Text 
DashPattern [r] r 

Instances

Instances details
Foldable IpeDash Source # 
Instance details

Defined in Ipe.Attributes

Methods

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

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

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

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

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

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

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

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

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

toList :: IpeDash a -> [a] #

null :: IpeDash a -> Bool #

length :: IpeDash a -> Int #

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

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

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

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

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

Traversable IpeDash Source # 
Instance details

Defined in Ipe.Attributes

Methods

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

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

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

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

Functor IpeDash Source # 
Instance details

Defined in Ipe.Attributes

Methods

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

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

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

Defined in Ipe.Attributes

Methods

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

show :: IpeDash r -> String #

showList :: [IpeDash r] -> ShowS #

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

Defined in Ipe.Attributes

Methods

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

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

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

Defined in Ipe.Reader

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

Defined in Ipe.Writer

data FillType Source #

Allowed Fill types

Constructors

Wind 
EOFill 

Instances

Instances details
Read FillType Source # 
Instance details

Defined in Ipe.Attributes

Show FillType Source # 
Instance details

Defined in Ipe.Attributes

Eq FillType Source # 
Instance details

Defined in Ipe.Attributes

IpeReadText FillType Source # 
Instance details

Defined in Ipe.Reader

IpeWriteText FillType Source # 
Instance details

Defined in Ipe.Writer

type IpeOpacity = Text Source #

IpeOpacity, IpeTyling, and IpeGradient are all symbolic values

data IpeArrow r Source #

Possible values for an ipe arrow

Constructors

IpeArrow 

Instances

Instances details
Foldable IpeArrow Source # 
Instance details

Defined in Ipe.Attributes

Methods

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

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

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

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

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

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

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

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

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

toList :: IpeArrow a -> [a] #

null :: IpeArrow a -> Bool #

length :: IpeArrow a -> Int #

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

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

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

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

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

Traversable IpeArrow Source # 
Instance details

Defined in Ipe.Attributes

Methods

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

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

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

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

Functor IpeArrow Source # 
Instance details

Defined in Ipe.Attributes

Methods

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

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

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

Defined in Ipe.Attributes

Methods

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

show :: IpeArrow r -> String #

showList :: [IpeArrow r] -> ShowS #

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

Defined in Ipe.Attributes

Methods

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

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

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

Defined in Ipe.Reader

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

Defined in Ipe.Writer

arrowSize :: forall r r. Lens (IpeArrow r) (IpeArrow r) (IpeSize r) (IpeSize r) Source #

arrowName :: forall r. Lens' (IpeArrow r) Text Source #

normalArrow :: IpeArrow r Source #

A normal arrow

Group Attributes

Attribute names in Ipe

class IpeAttrName (a :: AttributeUniverse) where Source #

For the types representing attribute values we can get the name/key to use when serializing to ipe.

Methods

attrName :: proxy a -> Text Source #

Instances

Instances details
IpeAttrName 'Arrow Source # 
Instance details

Defined in Ipe.Attributes

Methods

attrName :: proxy 'Arrow -> Text Source #

IpeAttrName 'Clip Source # 
Instance details

Defined in Ipe.Attributes

Methods

attrName :: proxy 'Clip -> Text Source #

IpeAttrName 'Dash Source # 
Instance details

Defined in Ipe.Attributes

Methods

attrName :: proxy 'Dash -> Text Source #

IpeAttrName 'Depth Source # 
Instance details

Defined in Ipe.Attributes

Methods

attrName :: proxy 'Depth -> Text Source #

IpeAttrName 'Fill Source # 
Instance details

Defined in Ipe.Attributes

Methods

attrName :: proxy 'Fill -> Text Source #

IpeAttrName 'FillRule Source # 
Instance details

Defined in Ipe.Attributes

Methods

attrName :: proxy 'FillRule -> Text Source #

IpeAttrName 'Gradient Source # 
Instance details

Defined in Ipe.Attributes

Methods

attrName :: proxy 'Gradient -> Text Source #

IpeAttrName 'HAlign Source # 
Instance details

Defined in Ipe.Attributes

Methods

attrName :: proxy 'HAlign -> Text Source #

IpeAttrName 'Height Source # 
Instance details

Defined in Ipe.Attributes

Methods

attrName :: proxy 'Height -> Text Source #

IpeAttrName 'Layer Source # 
Instance details

Defined in Ipe.Attributes

Methods

attrName :: proxy 'Layer -> Text Source #

IpeAttrName 'LineCap Source # 
Instance details

Defined in Ipe.Attributes

Methods

attrName :: proxy 'LineCap -> Text Source #

IpeAttrName 'LineJoin Source # 
Instance details

Defined in Ipe.Attributes

Methods

attrName :: proxy 'LineJoin -> Text Source #

IpeAttrName 'Matrix Source # 
Instance details

Defined in Ipe.Attributes

Methods

attrName :: proxy 'Matrix -> Text Source #

IpeAttrName 'Opacity Source # 
Instance details

Defined in Ipe.Attributes

Methods

attrName :: proxy 'Opacity -> Text Source #

IpeAttrName 'Pen Source # 
Instance details

Defined in Ipe.Attributes

Methods

attrName :: proxy 'Pen -> Text Source #

IpeAttrName 'Pin Source # 
Instance details

Defined in Ipe.Attributes

Methods

attrName :: proxy 'Pin -> Text Source #

IpeAttrName 'RArrow Source # 
Instance details

Defined in Ipe.Attributes

Methods

attrName :: proxy 'RArrow -> Text Source #

IpeAttrName 'Size Source # 
Instance details

Defined in Ipe.Attributes

Methods

attrName :: proxy 'Size -> Text Source #

IpeAttrName 'Stroke Source # 
Instance details

Defined in Ipe.Attributes

Methods

attrName :: proxy 'Stroke -> Text Source #

IpeAttrName 'StrokeOpacity Source # 
Instance details

Defined in Ipe.Attributes

Methods

attrName :: proxy 'StrokeOpacity -> Text Source #

IpeAttrName 'Style Source # 
Instance details

Defined in Ipe.Attributes

Methods

attrName :: proxy 'Style -> Text Source #

IpeAttrName 'Tiling Source # 
Instance details

Defined in Ipe.Attributes

Methods

attrName :: proxy 'Tiling -> Text Source #

IpeAttrName 'Transformations Source # 
Instance details

Defined in Ipe.Attributes

Methods

attrName :: proxy 'Transformations -> Text Source #

IpeAttrName 'VAlign Source # 
Instance details

Defined in Ipe.Attributes

Methods

attrName :: proxy 'VAlign -> Text Source #

IpeAttrName 'Width Source # 
Instance details

Defined in Ipe.Attributes

Methods

attrName :: proxy 'Width -> Text Source #

writeAttrNames :: AllConstrained IpeAttrName rs => Rec f rs -> Rec (Const Text) rs Source #

Writing Attribute names