Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data AttributeUniverse
- type LayerSym0 = Layer
- type MatrixSym0 = Matrix
- type PinSym0 = Pin
- type TransformationsSym0 = Transformations
- type StrokeSym0 = Stroke
- type FillSym0 = Fill
- type PenSym0 = Pen
- type SizeSym0 = Size
- type DashSym0 = Dash
- type LineCapSym0 = LineCap
- type LineJoinSym0 = LineJoin
- type FillRuleSym0 = FillRule
- type ArrowSym0 = Arrow
- type RArrowSym0 = RArrow
- type OpacitySym0 = Opacity
- type TilingSym0 = Tiling
- type GradientSym0 = Gradient
- type ClipSym0 = Clip
- type SAttributeUniverse = (Sing :: AttributeUniverse -> Type)
- type CommonAttributes = '[Layer, Matrix, Pin, Transformations]
- type TextLabelAttributes = CommonAttributes
- type MiniPageAttributes = CommonAttributes
- type ImageAttributes = CommonAttributes
- type SymbolAttributes = CommonAttributes ++ '[Stroke, Fill, Pen, Size]
- type PathAttributes = CommonAttributes ++ '[Stroke, Fill, Dash, Pen, LineCap, LineJoin, FillRule, Arrow, RArrow, Opacity, Tiling, Gradient]
- type GroupAttributes = CommonAttributes ++ '[Clip]
- newtype Attr f label = GAttr {}
- getAttr :: forall f label f label. Iso (Attr f label) (Attr f label) (Maybe (Apply f label :: Type)) (Maybe (Apply f label :: Type))
- pattern Attr :: forall u t t1. Apply u * t1 t -> Attr u t1 t
- pattern NoAttr :: forall u t t1. Attr u t1 t
- newtype Attributes f ats = Attrs {}
- 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)
- zipRecsWith :: (forall a. f a -> g a -> h a) -> Rec f as -> Rec g as -> Rec h as
- attrLens :: at ∈ ats => proxy at -> Lens' (Attributes f ats) (Maybe (Apply f at))
- lookupAttr :: at ∈ ats => proxy at -> Attributes f ats -> Maybe (Apply f at)
- setAttr :: forall proxy at ats f. at ∈ ats => proxy at -> Apply f at -> Attributes f ats -> Attributes f ats
- takeAttr :: forall proxy at ats f. at ∈ ats => proxy at -> Attributes f ats -> (Maybe (Apply f at), Attributes f ats)
- unSetAttr :: forall proxy at ats f. at ∈ ats => proxy at -> Attributes f ats -> Attributes f ats
- attr :: (at ∈ ats, RecApplicative ats) => proxy at -> Apply f at -> Attributes f ats
- data PinType
- = No
- | Yes
- | Horizontal
- | Vertical
- data TransformationTypes
- = Affine
- | Rigid
- | Translations
- data IpeValue v
- type Colour = Text
- newtype IpeSize r = IpeSize (IpeValue r)
- newtype IpePen r = IpePen (IpeValue r)
- newtype IpeColor = IpeColor (IpeValue Colour)
- data IpeDash r
- = DashNamed Text
- | DashPattern [r] r
- data FillType
- type IpeOpacity = Text
- type IpeTiling = Text
- type IpeGradient = Text
- data IpeArrow r = IpeArrow {
- _arrowName :: Text
- _arrowSize :: IpeSize r
- arrowSize :: forall r r. Lens (IpeArrow r) (IpeArrow r) (IpeSize r) (IpeSize r)
- arrowName :: forall r. Lens' (IpeArrow r) Text
- normalArrow :: IpeArrow r
- class IpeAttrName a where
- data GDict c a where
- type family AllSatisfy (c :: k -> Constraint) (xs :: [k]) :: Constraint where ...
- writeAttrNames :: AllSatisfy IpeAttrName rs => Rec f rs -> Rec (Const Text) rs
Documentation
data AttributeUniverse Source #
Layer | |
Matrix | |
Pin | |
Transformations | |
Stroke | |
Fill | |
Pen | |
Size | |
Dash | |
LineCap | |
LineJoin | |
FillRule | |
Arrow | |
RArrow | |
Opacity | |
Tiling | |
Gradient | |
Clip |
type MatrixSym0 = Matrix Source #
type StrokeSym0 = Stroke Source #
type LineCapSym0 = LineCap Source #
type LineJoinSym0 = LineJoin Source #
type FillRuleSym0 = FillRule Source #
type RArrowSym0 = RArrow Source #
type OpacitySym0 = Opacity Source #
type TilingSym0 = Tiling Source #
type GradientSym0 = Gradient Source #
type SAttributeUniverse = (Sing :: AttributeUniverse -> Type) Source #
type CommonAttributes = '[Layer, Matrix, Pin, Transformations] Source #
type ImageAttributes = CommonAttributes Source #
type SymbolAttributes = CommonAttributes ++ '[Stroke, Fill, Pen, Size] Source #
type PathAttributes = CommonAttributes ++ '[Stroke, Fill, Dash, Pen, LineCap, LineJoin, FillRule, Arrow, RArrow, Opacity, Tiling, Gradient] Source #
type GroupAttributes = CommonAttributes ++ '[Clip] Source #
Attr implements the mapping from labels to types as specified by the
(symbol representing) the type family f
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 u f l) Source # | Give pref. to the *RIGHT* |
IpeReadText (Apply u * f at) => IpeReadAttr (Attr u f at) Source # | |
IpeWriteText (Apply u * f at) => IpeWriteText (Attr u f at) 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 #
newtype Attributes f ats Source #
(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 # | |
RecAll u (Attr u f) ats Show => Show (Attributes u f ats) Source # | |
Semigroup (Attributes u f ats) Source # | |
RecApplicative u ats => Monoid (Attributes u f ats) Source # | |
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 #
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 #
Common Attributes
Possible values for Pin
data TransformationTypes Source #
Possible values for Transformation
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
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
DashNamed Text | |
DashPattern [r] r |
Eq r => Eq (IpeDash r) Source # | |
Show r => Show (IpeDash r) Source # | |
Coordinate r => IpeReadText (IpeDash r) Source # | |
IpeWriteText r => IpeWriteText (IpeDash r) Source # | |
Allowed Fill types
type IpeOpacity = Text Source #
IpeOpacity, IpeTyling, and IpeGradient are all symbolic values
type IpeGradient = Text Source #
Possible values for an ipe arrow
IpeArrow | |
|
Eq r => Eq (IpeArrow r) Source # | |
Show r => Show (IpeArrow r) Source # | |
Coordinate r => IpeReadText (IpeArrow r) Source # | |
IpeWriteText r => IpeWriteText (IpeArrow r) Source # | |
normalArrow :: IpeArrow r 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.
Wrap up a value with a capability given by its type
type family AllSatisfy (c :: k -> Constraint) (xs :: [k]) :: Constraint where ... Source #
Function that states that all elements in xs satisfy a given constraint c
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