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

Data.Geometry.Ipe.Attributes

Description

Possible Attributes we can assign to items in an Ipe file

Synopsis

Documentation

data AttributeUniverse Source #

Instances

Instances details
Eq AttributeUniverse Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Read AttributeUniverse Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Show AttributeUniverse Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

SingKind AttributeUniverse Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Associated Types

type Demote AttributeUniverse = (r :: Type) #

SingI 'Layer Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

sing :: Sing 'Layer #

SingI 'Matrix Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

sing :: Sing 'Matrix #

SingI 'Pin Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

sing :: Sing 'Pin #

SingI 'Transformations Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

SingI 'Stroke Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

sing :: Sing 'Stroke #

SingI 'Fill Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

sing :: Sing 'Fill #

SingI 'Pen Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

sing :: Sing 'Pen #

SingI 'Size Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

sing :: Sing 'Size #

SingI 'Dash Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

sing :: Sing 'Dash #

SingI 'LineCap Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

sing :: Sing 'LineCap #

SingI 'LineJoin Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

sing :: Sing 'LineJoin #

SingI 'FillRule Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

sing :: Sing 'FillRule #

SingI 'Arrow Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

sing :: Sing 'Arrow #

SingI 'RArrow Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

sing :: Sing 'RArrow #

SingI 'Opacity Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

sing :: Sing 'Opacity #

SingI 'Tiling Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

sing :: Sing 'Tiling #

SingI 'Gradient Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

sing :: Sing 'Gradient #

SingI 'Clip Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

sing :: Sing 'Clip #

(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 Data.Geometry.Ipe.Writer

Methods

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

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

Defined in Data.Geometry.Ipe.Content

type Sing Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

type Demote AttributeUniverse Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

type Apply (AttrMapSym1 a6989586621679194633 :: TyFun AttributeUniverse Type -> Type) (a6989586621679194634 :: AttributeUniverse) Source # 
Instance details

Defined in Data.Geometry.Ipe.Content

type Apply (AttrMapSym1 a6989586621679194633 :: TyFun AttributeUniverse Type -> Type) (a6989586621679194634 :: AttributeUniverse)

Attr

newtype Attr (f :: TyFun u * -> *) (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
Eq (Apply f label) => Eq (Attr f label) Source # 
Instance details

Defined in Data.Geometry.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 Data.Geometry.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 #

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

Defined in Data.Geometry.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 Data.Geometry.Ipe.Attributes

Methods

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

show :: Attr f label -> String #

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

Semigroup (Attr f l) Source #

Give pref. to the *RIGHT*

Instance details

Defined in Data.Geometry.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 #

Monoid (Attr f l) Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

mempty :: Attr f l #

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

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

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

Defined in Data.Geometry.Ipe.Reader

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

Defined in Data.Geometry.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 #

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 * -> *) (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 Data.Geometry.Ipe.Writer

Methods

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

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

Defined in Data.Geometry.Ipe.Attributes

Methods

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

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

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

Defined in Data.Geometry.Ipe.Attributes

Methods

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

show :: Attributes f ats -> String #

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

Semigroup (Attributes f ats) Source # 
Instance details

Defined in Data.Geometry.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 #

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

Defined in Data.Geometry.Ipe.Attributes

Methods

mempty :: Attributes f ats #

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

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

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

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

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

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

data PinType Source #

Common Attributes

Possible values for Pin

Constructors

No 
Yes 
Horizontal 
Vertical 

newtype IpeSize r Source #

TODO

Symbol Attributes

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

Constructors

IpeSize (IpeValue r) 

Instances

Instances details
Functor IpeSize Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

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

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

Foldable IpeSize Source # 
Instance details

Defined in Data.Geometry.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 Data.Geometry.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) #

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

Defined in Data.Geometry.Ipe.Attributes

Methods

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

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

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

Defined in Data.Geometry.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 #

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

Defined in Data.Geometry.Ipe.Attributes

Methods

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

show :: IpeSize r -> String #

showList :: [IpeSize r] -> ShowS #

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

Defined in Data.Geometry.Ipe.Reader

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

Defined in Data.Geometry.Ipe.Writer

newtype IpePen r Source #

Constructors

IpePen (IpeValue r) 

Instances

Instances details
Functor IpePen Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

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

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

Foldable IpePen Source # 
Instance details

Defined in Data.Geometry.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 Data.Geometry.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) #

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

Defined in Data.Geometry.Ipe.Attributes

Methods

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

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

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

Defined in Data.Geometry.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 #

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

Defined in Data.Geometry.Ipe.Attributes

Methods

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

show :: IpePen r -> String #

showList :: [IpePen r] -> ShowS #

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

Defined in Data.Geometry.Ipe.Reader

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

Defined in Data.Geometry.Ipe.Writer

data IpeDash r Source #

Path Attributes

Possible attributes for a path data PathAttributeUniverse = Stroke | Fill | Dash | Pen | LineCap | LineJoin | FillRule | Arrow | RArrow | Opacity | Tiling | Gradient deriving (Show,Eq)

Possible values for Dash

Constructors

DashNamed Text 
DashPattern [r] r 

Instances

Instances details
Functor IpeDash Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

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

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

Foldable IpeDash Source # 
Instance details

Defined in Data.Geometry.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 Data.Geometry.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) #

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

Defined in Data.Geometry.Ipe.Attributes

Methods

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

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

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

Defined in Data.Geometry.Ipe.Attributes

Methods

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

show :: IpeDash r -> String #

showList :: [IpeDash r] -> ShowS #

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

Defined in Data.Geometry.Ipe.Reader

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

Defined in Data.Geometry.Ipe.Writer

data FillType Source #

Allowed Fill types

Constructors

Wind 
EOFill 

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
Functor IpeArrow Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

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

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

Foldable IpeArrow Source # 
Instance details

Defined in Data.Geometry.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 Data.Geometry.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) #

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

Defined in Data.Geometry.Ipe.Attributes

Methods

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

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

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

Defined in Data.Geometry.Ipe.Attributes

Methods

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

show :: IpeArrow r -> String #

showList :: [IpeArrow r] -> ShowS #

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

Defined in Data.Geometry.Ipe.Reader

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

Defined in Data.Geometry.Ipe.Writer

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

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

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 'Layer Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

attrName :: proxy 'Layer -> Text Source #

IpeAttrName 'Matrix Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

attrName :: proxy 'Matrix -> Text Source #

IpeAttrName 'Pin Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

attrName :: proxy 'Pin -> Text Source #

IpeAttrName 'Transformations Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

attrName :: proxy 'Transformations -> Text Source #

IpeAttrName 'Stroke Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

attrName :: proxy 'Stroke -> Text Source #

IpeAttrName 'Fill Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

attrName :: proxy 'Fill -> Text Source #

IpeAttrName 'Pen Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

attrName :: proxy 'Pen -> Text Source #

IpeAttrName 'Size Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

attrName :: proxy 'Size -> Text Source #

IpeAttrName 'Dash Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

attrName :: proxy 'Dash -> Text Source #

IpeAttrName 'LineCap Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

attrName :: proxy 'LineCap -> Text Source #

IpeAttrName 'LineJoin Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

attrName :: proxy 'LineJoin -> Text Source #

IpeAttrName 'FillRule Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

attrName :: proxy 'FillRule -> Text Source #

IpeAttrName 'Arrow Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

attrName :: proxy 'Arrow -> Text Source #

IpeAttrName 'RArrow Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

attrName :: proxy 'RArrow -> Text Source #

IpeAttrName 'Opacity Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

attrName :: proxy 'Opacity -> Text Source #

IpeAttrName 'Tiling Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

attrName :: proxy 'Tiling -> Text Source #

IpeAttrName 'Gradient Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

attrName :: proxy 'Gradient -> Text Source #

IpeAttrName 'Clip Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

attrName :: proxy 'Clip -> Text Source #

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

Writing Attribute names