hgeometry-0.5.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 
SingI AttributeUniverse Layer Source 
SingI AttributeUniverse Matrix Source 
SingI AttributeUniverse Pin Source 
SingI AttributeUniverse Transformations Source 
SingI AttributeUniverse Stroke Source 
SingI AttributeUniverse Fill Source 
SingI AttributeUniverse Pen Source 
SingI AttributeUniverse Size Source 
SingI AttributeUniverse Dash Source 
SingI AttributeUniverse LineCap Source 
SingI AttributeUniverse LineJoin Source 
SingI AttributeUniverse FillRule Source 
SingI AttributeUniverse Arrow Source 
SingI AttributeUniverse RArrow Source 
SingI AttributeUniverse Opacity Source 
SingI AttributeUniverse Tiling Source 
SingI AttributeUniverse Gradient Source 
SingI AttributeUniverse Clip Source 
SingKind AttributeUniverse (KProxy AttributeUniverse) Source 
(AllSatisfy AttributeUniverse IpeAttrName rs, RecAll AttributeUniverse (Attr AttributeUniverse f) rs IpeWriteText, IpeWrite g) => IpeWrite ((:+) g (Attributes AttributeUniverse f rs)) Source 
SuppressUnusedWarnings (* -> TyFun AttributeUniverse * -> *) AttrMapSym1 
SuppressUnusedWarnings (TyFun * (TyFun AttributeUniverse * -> *) -> *) AttrMapSym0 
data Sing AttributeUniverse where Source 
type Apply * AttributeUniverse (AttrMapSym1 l1) l0 = AttrMapSym2 l1 l0 
type DemoteRep AttributeUniverse (KProxy AttributeUniverse) = AttributeUniverse Source 
type Apply (TyFun AttributeUniverse * -> *) * AttrMapSym0 l0 = AttrMapSym1 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

_getAttr :: Maybe (Apply f label)
 

Instances

Eq (Apply * u f label) => Eq (Attr u f label) Source 
Ord (Apply * u f label) => Ord (Attr u f label) Source 
Read (Apply * u f label) => Read (Attr u f label) Source 
Show (Apply * u f label) => Show (Attr u f label) Source 
Monoid (Attr k f l) Source

Give pref. to the *RIGHT*

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

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 * k t t -> Attr k t t Source

pattern NoAttr :: Attr k t t Source

newtype Attributes f ats Source

Constructors

Attrs 

Fields

_unAttrs :: Rec (Attr f) ats
 

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

newtype IpeSize r Source

Constructors

IpeSize (IpeValue r) 

newtype IpePen r Source

Constructors

IpePen (IpeValue r) 

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

Attribute names in Ipe

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 xs :: Constraint 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