hgeometry-0.7.0.0: Geometric Algorithms, Data structures, and Data types.

Safe HaskellNone
LanguageHaskell2010

Data.Geometry.Ipe.Attributes

Contents

Synopsis

Documentation

data AttributeUniverse Source #

Instances
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 :: *) #

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 #

(AllSatisfy IpeAttrName 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 # 
Instance details

Defined in Data.Geometry.Ipe.Types

SuppressUnusedWarnings AttrMapSym0 # 
Instance details

Defined in Data.Geometry.Ipe.Types

data Sing (z :: AttributeUniverse) Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

type Demote AttributeUniverse Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

type Apply (AttrMapSym1 l1 :: TyFun AttributeUniverse Type -> *) (l2 :: AttributeUniverse) # 
Instance details

Defined in Data.Geometry.Ipe.Types

type Apply AttrMapSym0 (l :: Type) # 
Instance details

Defined in Data.Geometry.Ipe.Types

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

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 #

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

Defined in Data.Geometry.Ipe.Reader

getAttr :: forall f label f label. Iso (Attr f label) (Attr f label) (Maybe (Apply f label)) (Maybe (Apply f label)) Source #

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

pattern NoAttr :: Attr f label Source #

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

Constructors

Attrs 

Fields

Instances
(AllSatisfy IpeAttrName 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 #

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 #

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 :: forall f ats f ats. Iso (Attributes f ats) (Attributes f ats) (Rec (Attr f) ats) (Rec (Attr f) ats) Source #

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

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

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

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

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 #

data PinType Source #

Common Attributes

Possible values for Pin

Constructors

No 
Yes 
Horizontal 
Vertical 

data IpeValue v Source #

TODO

Symbol Attributes

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

Many types either consist of a symbolc value, or a value of type v

Constructors

Named Text 
Valued v 
Instances
Functor IpeValue Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

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

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

Foldable IpeValue Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

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

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

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

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

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

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

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

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

toList :: IpeValue a -> [a] #

null :: IpeValue a -> Bool #

length :: IpeValue a -> Int #

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

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

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

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

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

Traversable IpeValue Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

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

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

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

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

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

Defined in Data.Geometry.Ipe.Attributes

Methods

(==) :: IpeValue v -> IpeValue v -> Bool #

(/=) :: IpeValue v -> IpeValue v -> Bool #

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

Defined in Data.Geometry.Ipe.Attributes

Methods

compare :: IpeValue v -> IpeValue v -> Ordering #

(<) :: IpeValue v -> IpeValue v -> Bool #

(<=) :: IpeValue v -> IpeValue v -> Bool #

(>) :: IpeValue v -> IpeValue v -> Bool #

(>=) :: IpeValue v -> IpeValue v -> Bool #

max :: IpeValue v -> IpeValue v -> IpeValue v #

min :: IpeValue v -> IpeValue v -> IpeValue v #

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

Defined in Data.Geometry.Ipe.Attributes

Methods

showsPrec :: Int -> IpeValue v -> ShowS #

show :: IpeValue v -> String #

showList :: [IpeValue v] -> ShowS #

IsString (IpeValue v) Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

fromString :: String -> IpeValue v #

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

Defined in Data.Geometry.Ipe.Writer

newtype IpeSize r Source #

Constructors

IpeSize (IpeValue r) 
Instances
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 #

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

Defined in Data.Geometry.Ipe.Writer

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

Defined in Data.Geometry.Ipe.Reader

newtype IpePen r Source #

Constructors

IpePen (IpeValue r) 
Instances
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 #

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

Defined in Data.Geometry.Ipe.Writer

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

Defined in Data.Geometry.Ipe.Reader

newtype IpeColor r Source #

Constructors

IpeColor (IpeValue (RGB r)) 
Instances
Eq r => Eq (IpeColor r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

Methods

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

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

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

Defined in Data.Geometry.Ipe.Attributes

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 #

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

Defined in Data.Geometry.Ipe.Attributes

Methods

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

show :: IpeColor r -> String #

showList :: [IpeColor r] -> ShowS #

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

Defined in Data.Geometry.Ipe.Writer

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

Defined in Data.Geometry.Ipe.Reader

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

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

Defined in Data.Geometry.Ipe.Writer

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

Defined in Data.Geometry.Ipe.Reader

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

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

Defined in Data.Geometry.Ipe.Writer

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

Defined in Data.Geometry.Ipe.Reader

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.

Minimal complete definition

attrName

Methods

attrName :: Proxy a -> Text Source #

Instances
IpeAttrName Layer Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

IpeAttrName Matrix Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

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

IpeAttrName Stroke Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

IpeAttrName Fill Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

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

IpeAttrName Dash Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

IpeAttrName LineCap Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

IpeAttrName LineJoin Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

IpeAttrName FillRule Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

IpeAttrName Arrow Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

IpeAttrName RArrow Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

IpeAttrName Opacity Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

IpeAttrName Tiling Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

IpeAttrName Gradient Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

IpeAttrName Clip Source # 
Instance details

Defined in Data.Geometry.Ipe.Attributes

type family AllSatisfy (c :: k -> Constraint) (xs :: [k]) :: Constraint where ... Source #

Function that states that all elements in xs satisfy a given constraint c

Equations

AllSatisfy c '[] = () 
AllSatisfy c (x ': xs) = (c x, AllSatisfy c xs) 

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

Writing Attribute names