Copyright | (C) Frank Staals |
---|---|
License | see the LICENSE file |
Maintainer | Frank Staals |
Safe Haskell | None |
Language | Haskell2010 |
Possible Attributes we can assign to items in an Ipe file
Synopsis
- 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 :: TyFun u * -> *) (label :: u) = GAttr {}
- getAttr :: forall f label f label. Iso (Attr f label) (Attr f label) (Maybe (Apply f label)) (Maybe (Apply f label))
- pattern Attr :: Apply f label -> Attr f label
- pattern NoAttr :: Attr f label
- traverseAttr :: Applicative h => (Apply f label -> h (Apply g label)) -> Attr f label -> h (Attr g label)
- pureAttr :: (Applicative h, Apply f a ~ Apply g a) => Attr f a -> h (Attr g a)
- newtype Attributes (f :: TyFun u * -> *) (ats :: [u]) = Attrs (Rec (Attr f) ats)
- unAttrs :: Lens (Attributes f ats) (Attributes f' ats') (Rec (Attr f) ats) (Rec (Attr f') ats')
- traverseAttrs :: Applicative h => (forall label. Attr f label -> h (Attr g label)) -> Attributes f ats -> h (Attributes g ats)
- zipRecsWith :: (forall a. f a -> g a -> h a) -> Rec f as -> Rec g as -> Rec h as
- ixAttr :: forall at ats proxy f. at ∈ ats => proxy at -> Lens' (Attributes f ats) (Maybe (Apply f at))
- _Attr :: forall at ats proxy f. (at ∈ ats, RecApplicative ats) => proxy at -> Prism' (Attributes f ats) (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
- newtype IpeSize r = IpeSize (IpeValue r)
- newtype IpePen r = IpePen (IpeValue r)
- 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 :: AttributeUniverse) where
- writeAttrNames :: AllConstrained 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 |
Instances
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
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
Instances
Eq (Apply f label) => Eq (Attr f label) Source # | |
Ord (Apply f label) => Ord (Attr f label) Source # | |
Defined in Data.Geometry.Ipe.Attributes | |
Read (Apply f label) => Read (Attr f label) Source # | |
Show (Apply f label) => Show (Attr f label) Source # | |
Semigroup (Attr f l) Source # | Give pref. to the *RIGHT* |
Monoid (Attr f l) Source # | |
IpeReadText (Apply f at) => IpeReadAttr (Attr f at) Source # | |
Defined in Data.Geometry.Ipe.Reader ipeReadAttr :: Text -> Node Text Text -> Either ConversionError (Attr f at) Source # | |
IpeWriteText (Apply f at) => IpeWriteText (Attr f at) Source # | |
Defined in Data.Geometry.Ipe.Writer |
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 #
Constructor for constructing an Attr given an actual value.
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.
Instances
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 #
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
Common Attributes
Possible values for Pin
data TransformationTypes Source #
Possible values for Transformation
Instances
Eq TransformationTypes Source # | |
Defined in Data.Geometry.Ipe.Attributes (==) :: TransformationTypes -> TransformationTypes -> Bool # (/=) :: TransformationTypes -> TransformationTypes -> Bool # | |
Read TransformationTypes Source # | |
Defined in Data.Geometry.Ipe.Attributes | |
Show TransformationTypes Source # | |
Defined in Data.Geometry.Ipe.Attributes showsPrec :: Int -> TransformationTypes -> ShowS # show :: TransformationTypes -> String # showList :: [TransformationTypes] -> ShowS # | |
IpeReadText TransformationTypes Source # | |
Defined in Data.Geometry.Ipe.Reader | |
IpeWriteText TransformationTypes Source # | |
Defined in Data.Geometry.Ipe.Writer |
TODO
Symbol Attributes
The optional Attributes for a symbol data SymbolAttributeUniverse = SymbolStroke | SymbolFill | SymbolPen | Size deriving (Show,Eq)
Instances
Functor IpeSize Source # | |
Foldable IpeSize Source # | |
Defined in Data.Geometry.Ipe.Attributes fold :: Monoid m => IpeSize m -> 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 # elem :: Eq a => a -> IpeSize a -> Bool # maximum :: Ord a => IpeSize a -> a # minimum :: Ord a => IpeSize a -> a # | |
Traversable IpeSize Source # | |
Eq r => Eq (IpeSize r) Source # | |
Ord r => Ord (IpeSize r) Source # | |
Defined in Data.Geometry.Ipe.Attributes | |
Show r => Show (IpeSize r) Source # | |
Coordinate r => IpeReadText (IpeSize r) Source # | |
Defined in Data.Geometry.Ipe.Reader ipeReadText :: Text -> Either ConversionError (IpeSize r) Source # | |
IpeWriteText r => IpeWriteText (IpeSize r) Source # | |
Defined in Data.Geometry.Ipe.Writer |
Instances
Functor IpePen Source # | |
Foldable IpePen Source # | |
Defined in Data.Geometry.Ipe.Attributes fold :: Monoid m => IpePen m -> 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 # elem :: Eq a => a -> IpePen a -> Bool # maximum :: Ord a => IpePen a -> a # minimum :: Ord a => IpePen a -> a # | |
Traversable IpePen Source # | |
Eq r => Eq (IpePen r) Source # | |
Ord r => Ord (IpePen r) Source # | |
Defined in Data.Geometry.Ipe.Attributes | |
Show r => Show (IpePen r) Source # | |
Coordinate r => IpeReadText (IpePen r) Source # | |
Defined in Data.Geometry.Ipe.Reader ipeReadText :: Text -> Either ConversionError (IpePen r) Source # | |
IpeWriteText r => IpeWriteText (IpePen r) Source # | |
Defined in Data.Geometry.Ipe.Writer |
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 |
Instances
Functor IpeDash Source # | |
Foldable IpeDash Source # | |
Defined in Data.Geometry.Ipe.Attributes fold :: Monoid m => IpeDash m -> 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 # elem :: Eq a => a -> IpeDash a -> Bool # maximum :: Ord a => IpeDash a -> a # minimum :: Ord a => IpeDash a -> a # | |
Traversable IpeDash Source # | |
Eq r => Eq (IpeDash r) Source # | |
Show r => Show (IpeDash r) Source # | |
Coordinate r => IpeReadText (IpeDash r) Source # | |
Defined in Data.Geometry.Ipe.Reader ipeReadText :: Text -> Either ConversionError (IpeDash r) Source # | |
IpeWriteText r => IpeWriteText (IpeDash r) Source # | |
Defined in Data.Geometry.Ipe.Writer |
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 | |
|
Instances
Functor IpeArrow Source # | |
Foldable IpeArrow Source # | |
Defined in Data.Geometry.Ipe.Attributes fold :: Monoid m => IpeArrow m -> 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 # elem :: Eq a => a -> IpeArrow a -> Bool # maximum :: Ord a => IpeArrow a -> a # minimum :: Ord a => IpeArrow a -> a # | |
Traversable IpeArrow Source # | |
Eq r => Eq (IpeArrow r) Source # | |
Show r => Show (IpeArrow r) Source # | |
Coordinate r => IpeReadText (IpeArrow r) Source # | |
Defined in Data.Geometry.Ipe.Reader ipeReadText :: Text -> Either ConversionError (IpeArrow r) Source # | |
IpeWriteText r => IpeWriteText (IpeArrow r) Source # | |
Defined in Data.Geometry.Ipe.Writer |
normalArrow :: IpeArrow r 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.
Instances
writeAttrNames :: AllConstrained IpeAttrName rs => Rec f rs -> Rec (Const Text) rs Source #
Writing Attribute names