hgeometry-0.6.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 # 
Read AttributeUniverse Source # 
Show AttributeUniverse Source # 
SingKind AttributeUniverse Source # 
SingI AttributeUniverse Layer Source # 

Methods

sing :: Sing Layer a #

SingI AttributeUniverse Matrix Source # 

Methods

sing :: Sing Matrix a #

SingI AttributeUniverse Pin Source # 

Methods

sing :: Sing Pin a #

SingI AttributeUniverse Transformations Source # 
SingI AttributeUniverse Stroke Source # 

Methods

sing :: Sing Stroke a #

SingI AttributeUniverse Fill Source # 

Methods

sing :: Sing Fill a #

SingI AttributeUniverse Pen Source # 

Methods

sing :: Sing Pen a #

SingI AttributeUniverse Size Source # 

Methods

sing :: Sing Size a #

SingI AttributeUniverse Dash Source # 

Methods

sing :: Sing Dash a #

SingI AttributeUniverse LineCap Source # 

Methods

sing :: Sing LineCap a #

SingI AttributeUniverse LineJoin Source # 

Methods

sing :: Sing LineJoin a #

SingI AttributeUniverse FillRule Source # 

Methods

sing :: Sing FillRule a #

SingI AttributeUniverse Arrow Source # 

Methods

sing :: Sing Arrow a #

SingI AttributeUniverse RArrow Source # 

Methods

sing :: Sing RArrow a #

SingI AttributeUniverse Opacity Source # 

Methods

sing :: Sing Opacity a #

SingI AttributeUniverse Tiling Source # 

Methods

sing :: Sing Tiling a #

SingI AttributeUniverse Gradient Source # 

Methods

sing :: Sing Gradient a #

SingI AttributeUniverse Clip Source # 

Methods

sing :: Sing Clip a #

(AllSatisfy AttributeUniverse IpeAttrName rs, RecAll AttributeUniverse (Attr AttributeUniverse f) rs IpeWriteText, IpeWrite g) => IpeWrite ((:+) g (Attributes AttributeUniverse f rs)) Source # 
SuppressUnusedWarnings (Type -> TyFun AttributeUniverse Type -> *) AttrMapSym1 # 
SuppressUnusedWarnings (TyFun Type (TyFun AttributeUniverse Type -> Type) -> *) AttrMapSym0 # 
data Sing AttributeUniverse Source # 
type DemoteRep AttributeUniverse Source # 
type Apply AttributeUniverse Type (AttrMapSym1 l1) l0 # 
type Apply Type (TyFun AttributeUniverse Type -> Type) AttrMapSym0 l0 # 

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

Methods

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

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

Ord (Apply u * f label) => Ord (Attr u f label) Source # 

Methods

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

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

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

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

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

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

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

Read (Apply u * f label) => Read (Attr u f label) Source # 

Methods

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

readList :: ReadS [Attr u f label] #

readPrec :: ReadPrec (Attr u f label) #

readListPrec :: ReadPrec [Attr u f label] #

Show (Apply u * f label) => Show (Attr u f label) Source # 

Methods

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

show :: Attr u f label -> String #

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

Monoid (Attr u f l) Source #

Give pref. to the *RIGHT*

Methods

mempty :: Attr u f l #

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

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

IpeReadText (Apply u * f at) => IpeReadAttr (Attr u f at) Source # 
IpeWriteText (Apply u * f at) => IpeWriteText (Attr u f at) Source # 

Methods

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

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

pattern Attr :: forall u t t1. Apply u * t1 t -> Attr u t1 t Source #

pattern NoAttr :: forall u t t1. Attr u t1 t Source #

newtype Attributes f ats Source #

Constructors

Attrs 

Fields

Instances

(AllSatisfy AttributeUniverse IpeAttrName rs, RecAll AttributeUniverse (Attr AttributeUniverse f) rs IpeWriteText, IpeWrite g) => IpeWrite ((:+) g (Attributes AttributeUniverse f rs)) Source # 
RecAll u (Attr u f) ats Eq => Eq (Attributes u f ats) Source # 

Methods

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

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

RecAll u (Attr u f) ats Show => Show (Attributes u f ats) Source # 

Methods

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

show :: Attributes u f ats -> String #

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

Semigroup (Attributes u f ats) Source # 

Methods

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

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

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

RecApplicative u ats => Monoid (Attributes u f ats) Source # 

Methods

mempty :: Attributes u f ats #

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

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

unAttrs :: forall f ats f ats. Iso (Attributes f ats) (Attributes f ats) (Rec (Attr f :: u -> Type) ats) (Rec (Attr f :: u -> Type) 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 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

Eq v => Eq (IpeValue v) Source # 

Methods

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

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

Ord v => Ord (IpeValue v) Source # 

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 # 

Methods

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

show :: IpeValue v -> String #

showList :: [IpeValue v] -> ShowS #

IsString (IpeValue v) Source # 

Methods

fromString :: String -> IpeValue v #

IpeWriteText v => IpeWriteText (IpeValue v) Source # 

newtype IpeSize r Source #

Constructors

IpeSize (IpeValue r) 

Instances

Eq r => Eq (IpeSize r) Source # 

Methods

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

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

Ord r => Ord (IpeSize r) Source # 

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 # 

Methods

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

show :: IpeSize r -> String #

showList :: [IpeSize r] -> ShowS #

Coordinate r => IpeReadText (IpeSize r) Source # 
IpeWriteText r => IpeWriteText (IpeSize r) Source # 

newtype IpePen r Source #

Constructors

IpePen (IpeValue r) 

Instances

Eq r => Eq (IpePen r) Source # 

Methods

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

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

Ord r => Ord (IpePen r) Source # 

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 # 

Methods

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

show :: IpePen r -> String #

showList :: [IpePen r] -> ShowS #

Coordinate r => IpeReadText (IpePen r) Source # 
IpeWriteText r => IpeWriteText (IpePen r) Source # 

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 

type IpeOpacity = Text Source #

IpeOpacity, IpeTyling, and IpeGradient are all symbolic values

data IpeArrow r Source #

Possible values for an ipe arrow

Constructors

IpeArrow 

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 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 # 
IpeAttrName Matrix Source # 
IpeAttrName Pin Source # 
IpeAttrName Transformations Source # 
IpeAttrName Stroke Source # 
IpeAttrName Fill Source # 
IpeAttrName Pen Source # 
IpeAttrName Size Source # 
IpeAttrName Dash Source # 
IpeAttrName LineCap Source # 
IpeAttrName LineJoin Source # 
IpeAttrName FillRule Source # 
IpeAttrName Arrow Source # 
IpeAttrName RArrow Source # 
IpeAttrName Opacity Source # 
IpeAttrName Tiling Source # 
IpeAttrName Gradient Source # 
IpeAttrName Clip Source # 

data GDict c a where Source #

Wrap up a value with a capability given by its type

Constructors

GDict :: c a => Proxy a -> GDict c a 

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