{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE UnicodeSyntax #-}
{-# LANGUAGE UndecidableInstances #-}
module Ipe.Attributes
where
import Control.Lens hiding (rmap, Const)
import Data.Kind (Type)
import Data.Singletons
import Data.Singletons.TH
import Data.Text (Text)
import Data.Vinyl
import Data.Vinyl.Functor
import Data.Vinyl.TypeLevel
import Ipe.Value
import Text.Read (lexP, step, parens, prec, (+++)
, Lexeme(Ident), readPrec, readListPrec, readListPrecDefault)
data AttributeUniverse =
Layer | Matrix | Pin | Transformations
| Stroke | Fill | Pen | Size
| Dash | LineCap | LineJoin
| FillRule | Arrow | RArrow | StrokeOpacity | Opacity | Tiling | Gradient
| Width | Height | Depth | VAlign | HAlign | Style
| Clip
deriving (Int -> AttributeUniverse -> ShowS
[AttributeUniverse] -> ShowS
AttributeUniverse -> String
(Int -> AttributeUniverse -> ShowS)
-> (AttributeUniverse -> String)
-> ([AttributeUniverse] -> ShowS)
-> Show AttributeUniverse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AttributeUniverse -> ShowS
showsPrec :: Int -> AttributeUniverse -> ShowS
$cshow :: AttributeUniverse -> String
show :: AttributeUniverse -> String
$cshowList :: [AttributeUniverse] -> ShowS
showList :: [AttributeUniverse] -> ShowS
Show,ReadPrec [AttributeUniverse]
ReadPrec AttributeUniverse
Int -> ReadS AttributeUniverse
ReadS [AttributeUniverse]
(Int -> ReadS AttributeUniverse)
-> ReadS [AttributeUniverse]
-> ReadPrec AttributeUniverse
-> ReadPrec [AttributeUniverse]
-> Read AttributeUniverse
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AttributeUniverse
readsPrec :: Int -> ReadS AttributeUniverse
$creadList :: ReadS [AttributeUniverse]
readList :: ReadS [AttributeUniverse]
$creadPrec :: ReadPrec AttributeUniverse
readPrec :: ReadPrec AttributeUniverse
$creadListPrec :: ReadPrec [AttributeUniverse]
readListPrec :: ReadPrec [AttributeUniverse]
Read,AttributeUniverse -> AttributeUniverse -> Bool
(AttributeUniverse -> AttributeUniverse -> Bool)
-> (AttributeUniverse -> AttributeUniverse -> Bool)
-> Eq AttributeUniverse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AttributeUniverse -> AttributeUniverse -> Bool
== :: AttributeUniverse -> AttributeUniverse -> Bool
$c/= :: AttributeUniverse -> AttributeUniverse -> Bool
/= :: AttributeUniverse -> AttributeUniverse -> Bool
Eq)
genSingletons [ ''AttributeUniverse ]
type CommonAttributes = [ Layer, Matrix, Pin, Transformations ]
type TextAttributes = CommonAttributes ++
[Stroke, Size, Width, Height, Depth, VAlign, HAlign, Style, Opacity]
type TextLabelAttributes = TextAttributes
type MiniPageAttributes = TextAttributes
type ImageAttributes = CommonAttributes
type SymbolAttributes = CommonAttributes ++ [Stroke, Fill, Pen, Size]
type PathAttributes = CommonAttributes ++
[ Stroke, Fill, Dash, Pen, LineCap, LineJoin
, FillRule, Arrow, RArrow, StrokeOpacity, Opacity, Tiling, Gradient
]
type GroupAttributes = CommonAttributes ++ '[ 'Clip]
newtype Attr (f :: TyFun u Type -> Type)
(label :: u) = GAttr { forall u (f :: TyFun u (*) -> *) (label :: u).
Attr f label -> Maybe (Apply f label)
_getAttr :: Maybe (Apply f label) }
deriving instance Eq (Apply f label) => Eq (Attr f label)
deriving instance Ord (Apply f label) => Ord (Attr f label)
makeLenses ''Attr
pattern Attr :: Apply f label -> Attr f label
pattern $mAttr :: forall {r} {u} {f :: u ~> *} {label :: u}.
Attr f label -> (Apply f label -> r) -> ((# #) -> r) -> r
$bAttr :: forall {u} (f :: u ~> *) (label :: u).
Apply f label -> Attr f label
Attr x = GAttr (Just x)
pattern NoAttr :: Attr f label
pattern $mNoAttr :: forall {r} {u} {f :: TyFun u (*) -> *} {label :: u}.
Attr f label -> ((# #) -> r) -> ((# #) -> r) -> r
$bNoAttr :: forall {u} (f :: TyFun u (*) -> *) (label :: u). Attr f label
NoAttr = GAttr Nothing
{-# COMPLETE NoAttr, Attr #-}
traverseAttr :: Applicative h => (Apply f label -> h (Apply g label))
-> Attr f label -> h (Attr g label)
traverseAttr :: forall {u} (h :: * -> *) (f :: u ~> *) (label :: u) (g :: u ~> *).
Applicative h =>
(Apply f label -> h (Apply g label))
-> Attr f label -> h (Attr g label)
traverseAttr Apply f label -> h (Apply g label)
f = \case
Attr Apply f label
x -> Apply g label -> Attr g label
forall {u} (f :: u ~> *) (label :: u).
Apply f label -> Attr f label
Attr (Apply g label -> Attr g label)
-> h (Apply g label) -> h (Attr g label)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Apply f label -> h (Apply g label)
f Apply f label
x
Attr f label
NoAttr -> Attr g label -> h (Attr g label)
forall a. a -> h a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Attr g label
forall {u} (f :: TyFun u (*) -> *) (label :: u). Attr f label
NoAttr
pureAttr :: (Applicative h, Apply f a ~ Apply g a) => Attr f a -> h (Attr g a)
pureAttr :: forall {u} (h :: * -> *) (f :: u ~> *) (a :: u) (g :: u ~> *).
(Applicative h, Apply f a ~ Apply g a) =>
Attr f a -> h (Attr g a)
pureAttr = Attr g a -> h (Attr g a)
forall a. a -> h a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Attr g a -> h (Attr g a))
-> (Attr f a -> Attr g a) -> Attr f a -> h (Attr g a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
Attr Apply f a
a -> Apply g a -> Attr g a
forall {u} (f :: u ~> *) (label :: u).
Apply f label -> Attr f label
Attr Apply f a
Apply g a
a
Attr f a
NoAttr -> Attr g a
forall {u} (f :: TyFun u (*) -> *) (label :: u). Attr f label
NoAttr
instance Show (Apply f label) => Show (Attr f label) where
showsPrec :: Int -> Attr f label -> ShowS
showsPrec Int
d Attr f label
NoAttr = Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
app_prec) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString String
"NoAttr"
where app_prec :: Int
app_prec = Int
10
showsPrec Int
d (Attr Apply f label
a) = Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
up_prec) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
String -> ShowS
showString String
"Attr " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Apply f label -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec (Int
up_precInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Apply f label
a
where up_prec :: Int
up_prec = Int
5
instance Read (Apply f label) => Read (Attr f label) where
readPrec :: ReadPrec (Attr f label)
readPrec = ReadPrec (Attr f label) -> ReadPrec (Attr f label)
forall a. ReadPrec a -> ReadPrec a
parens (ReadPrec (Attr f label) -> ReadPrec (Attr f label))
-> ReadPrec (Attr f label) -> ReadPrec (Attr f label)
forall a b. (a -> b) -> a -> b
$ (Int -> ReadPrec (Attr f label) -> ReadPrec (Attr f label)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
app_prec (ReadPrec (Attr f label) -> ReadPrec (Attr f label))
-> ReadPrec (Attr f label) -> ReadPrec (Attr f label)
forall a b. (a -> b) -> a -> b
$ do
Ident "NoAttr" <- ReadPrec Lexeme
lexP
pure NoAttr)
ReadPrec (Attr f label)
-> ReadPrec (Attr f label) -> ReadPrec (Attr f label)
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++ (Int -> ReadPrec (Attr f label) -> ReadPrec (Attr f label)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
up_prec (ReadPrec (Attr f label) -> ReadPrec (Attr f label))
-> ReadPrec (Attr f label) -> ReadPrec (Attr f label)
forall a b. (a -> b) -> a -> b
$ do
Ident "Attr" <- ReadPrec Lexeme
lexP
a <- step readPrec
pure $ Attr a)
where
app_prec :: Int
app_prec = Int
10
up_prec :: Int
up_prec = Int
5
readListPrec :: ReadPrec [Attr f label]
readListPrec = ReadPrec [Attr f label]
forall a. Read a => ReadPrec [a]
readListPrecDefault
instance Semigroup (Attr f l) where
Attr f l
_ <> :: Attr f l -> Attr f l -> Attr f l
<> b :: Attr f l
b@(Attr Apply f l
_) = Attr f l
b
Attr f l
a <> Attr f l
_ = Attr f l
a
instance Monoid (Attr f l) where
mempty :: Attr f l
mempty = Attr f l
forall {u} (f :: TyFun u (*) -> *) (label :: u). Attr f label
NoAttr
newtype Attributes (f :: TyFun u Type -> Type) (ats :: [u]) = Attrs (Rec (Attr f) ats)
unAttrs :: Lens (Attributes f ats) (Attributes f' ats') (Rec (Attr f) ats) (Rec (Attr f') ats')
unAttrs :: forall {u} {u} (f :: TyFun u (*) -> *) (ats :: [u])
(f' :: TyFun u (*) -> *) (ats' :: [u]) (f :: * -> *).
Functor f =>
(Rec (Attr f) ats -> f (Rec (Attr f') ats'))
-> Attributes f ats -> f (Attributes f' ats')
unAttrs = (Attributes f ats -> Rec (Attr f) ats)
-> (Attributes f ats -> Rec (Attr f') ats' -> Attributes f' ats')
-> Lens
(Attributes f ats)
(Attributes f' ats')
(Rec (Attr f) ats)
(Rec (Attr f') ats')
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\(Attrs Rec (Attr f) ats
r) -> Rec (Attr f) ats
r) ((Rec (Attr f') ats' -> Attributes f' ats')
-> Attributes f ats -> Rec (Attr f') ats' -> Attributes f' ats'
forall a b. a -> b -> a
const Rec (Attr f') ats' -> Attributes f' ats'
forall u (f :: TyFun u (*) -> *) (ats :: [u]).
Rec (Attr f) ats -> Attributes f ats
Attrs)
deriving instance ( RMap ats, ReifyConstraint Show (Attr f) ats, RecordToList ats
, RecAll (Attr f) ats Show) => Show (Attributes f ats)
instance ( ReifyConstraint Eq (Attr f) ats, RecordToList ats
, RecAll (Attr f) ats Eq) => Eq (Attributes f ats) where
(Attrs Rec (Attr f) ats
a) == :: Attributes f ats -> Attributes f ats -> Bool
== (Attrs Rec (Attr f) ats
b) = [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and ([Bool] -> Bool)
-> (Rec (Attr f) ats -> [Bool]) -> Rec (Attr f) ats -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rec (Const Bool) ats -> [Bool]
forall a. Rec (Const a) ats -> [a]
forall {u} (rs :: [u]) a.
RecordToList rs =>
Rec (Const a) rs -> [a]
recordToList
(Rec (Const Bool) ats -> [Bool])
-> (Rec (Attr f) ats -> Rec (Const Bool) ats)
-> Rec (Attr f) ats
-> [Bool]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall (a :: u).
Attr f a -> (:.) (Dict Eq) (Attr f) a -> Const Bool a)
-> Rec (Attr f) ats
-> Rec (Dict Eq :. Attr f) ats
-> Rec (Const Bool) ats
forall {u} (f :: u -> *) (g :: u -> *) (h :: u -> *) (as :: [u]).
(forall (a :: u). f a -> g a -> h a)
-> Rec f as -> Rec g as -> Rec h as
zipRecsWith (\Attr f a
x (Compose (Dict Attr f a
y)) -> Bool -> Const Bool a
forall k a (b :: k). a -> Const a b
Const (Bool -> Const Bool a) -> Bool -> Const Bool a
forall a b. (a -> b) -> a -> b
$ Attr f a
x Attr f a -> Attr f a -> Bool
forall a. Eq a => a -> a -> Bool
== Attr f a
y) Rec (Attr f) ats
a
(Rec (Dict Eq :. Attr f) ats -> Rec (Const Bool) ats)
-> (Rec (Attr f) ats -> Rec (Dict Eq :. Attr f) ats)
-> Rec (Attr f) ats
-> Rec (Const Bool) ats
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall {u} (c :: * -> Constraint) (f :: u -> *) (rs :: [u]).
ReifyConstraint c f rs =>
Rec f rs -> Rec (Dict c :. f) rs
forall (c :: * -> Constraint) (f :: u -> *) (rs :: [u]).
ReifyConstraint c f rs =>
Rec f rs -> Rec (Dict c :. f) rs
reifyConstraint @Eq) (Rec (Attr f) ats -> Bool) -> Rec (Attr f) ats -> Bool
forall a b. (a -> b) -> a -> b
$ Rec (Attr f) ats
b
instance RecApplicative ats => Monoid (Attributes f ats) where
mempty :: Attributes f ats
mempty = Rec (Attr f) ats -> Attributes f ats
forall u (f :: TyFun u (*) -> *) (ats :: [u]).
Rec (Attr f) ats -> Attributes f ats
Attrs (Rec (Attr f) ats -> Attributes f ats)
-> Rec (Attr f) ats -> Attributes f ats
forall a b. (a -> b) -> a -> b
$ (forall (x :: u). Attr f x) -> Rec (Attr f) ats
forall {u} (rs :: [u]) (f :: u -> *).
RecApplicative rs =>
(forall (x :: u). f x) -> Rec f rs
forall (f :: u -> *). (forall (x :: u). f x) -> Rec f ats
rpure Attr f x
forall (x :: u). Attr f x
forall a. Monoid a => a
mempty
instance Semigroup (Attributes f ats) where
(Attrs Rec (Attr f) ats
as) <> :: Attributes f ats -> Attributes f ats -> Attributes f ats
<> (Attrs Rec (Attr f) ats
bs) = Rec (Attr f) ats -> Attributes f ats
forall u (f :: TyFun u (*) -> *) (ats :: [u]).
Rec (Attr f) ats -> Attributes f ats
Attrs (Rec (Attr f) ats -> Attributes f ats)
-> Rec (Attr f) ats -> Attributes f ats
forall a b. (a -> b) -> a -> b
$ (forall (a :: u). Attr f a -> Attr f a -> Attr f a)
-> Rec (Attr f) ats -> Rec (Attr f) ats -> Rec (Attr f) ats
forall {u} (f :: u -> *) (g :: u -> *) (h :: u -> *) (as :: [u]).
(forall (a :: u). f a -> g a -> h a)
-> Rec f as -> Rec g as -> Rec h as
zipRecsWith Attr f a -> Attr f a -> Attr f a
forall (a :: u). Attr f a -> Attr f a -> Attr f a
forall a. Semigroup a => a -> a -> a
(<>) Rec (Attr f) ats
as Rec (Attr f) ats
bs
traverseAttrs :: Applicative h
=> (forall label. Attr f label -> h (Attr g label))
-> Attributes f ats -> h (Attributes g ats)
traverseAttrs :: forall {u} (h :: * -> *) (f :: TyFun u (*) -> *)
(g :: TyFun u (*) -> *) (ats :: [u]).
Applicative h =>
(forall (label :: u). Attr f label -> h (Attr g label))
-> Attributes f ats -> h (Attributes g ats)
traverseAttrs forall (label :: u). Attr f label -> h (Attr g label)
f (Attrs Rec (Attr f) ats
ats) = Rec (Attr g) ats -> Attributes g ats
forall u (f :: TyFun u (*) -> *) (ats :: [u]).
Rec (Attr f) ats -> Attributes f ats
Attrs (Rec (Attr g) ats -> Attributes g ats)
-> h (Rec (Attr g) ats) -> h (Attributes g ats)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (label :: u). Attr f label -> h (Attr g label))
-> Rec (Attr f) ats -> h (Rec (Attr g) ats)
forall {u} (h :: * -> *) (f :: u -> *) (g :: u -> *) (rs :: [u]).
Applicative h =>
(forall (x :: u). f x -> h (g x)) -> Rec f rs -> h (Rec g rs)
rtraverse Attr f x -> h (Attr g x)
forall (label :: u). Attr f label -> h (Attr g label)
f Rec (Attr f) ats
ats
zipRecsWith :: (forall a. f a -> g a -> h a)
-> Rec f as -> Rec g as -> Rec h as
zipRecsWith :: forall {u} (f :: u -> *) (g :: u -> *) (h :: u -> *) (as :: [u]).
(forall (a :: u). f a -> g a -> h a)
-> Rec f as -> Rec g as -> Rec h as
zipRecsWith forall (a :: u). f a -> g a -> h a
_ Rec f as
RNil Rec g as
_ = Rec h as
Rec h '[]
forall {u} (a :: u -> *). Rec a '[]
RNil
zipRecsWith forall (a :: u). f a -> g a -> h a
f (f r
r :& Rec f rs
rs) (g r
s :& Rec g rs
ss) = f r -> g r -> h r
forall (a :: u). f a -> g a -> h a
f f r
r g r
g r
s h r -> Rec h rs -> Rec h (r : rs)
forall {u} (a :: u -> *) (r :: u) (rs :: [u]).
a r -> Rec a rs -> Rec a (r : rs)
:& (forall (a :: u). f a -> g a -> h a)
-> Rec f rs -> Rec g rs -> Rec h rs
forall {u} (f :: u -> *) (g :: u -> *) (h :: u -> *) (as :: [u]).
(forall (a :: u). f a -> g a -> h a)
-> Rec f as -> Rec g as -> Rec h as
zipRecsWith f a -> g a -> h a
forall (a :: u). f a -> g a -> h a
f Rec f rs
rs Rec g rs
Rec g rs
ss
ixAttr :: forall at ats proxy f. (at ∈ ats)
=> proxy at -> Lens' (Attributes f ats) (Maybe (Apply f at))
ixAttr :: forall {k1} (at :: k1) (ats :: [k1]) (proxy :: k1 -> *)
(f :: TyFun k1 (*) -> *).
(at ∈ ats) =>
proxy at -> Lens' (Attributes f ats) (Maybe (Apply f at))
ixAttr proxy at
_ = (Rec (Attr f) ats -> f (Rec (Attr f) ats))
-> Attributes f ats -> f (Attributes f ats)
forall {u} {u} (f :: TyFun u (*) -> *) (ats :: [u])
(f' :: TyFun u (*) -> *) (ats' :: [u]) (f :: * -> *).
Functor f =>
(Rec (Attr f) ats -> f (Rec (Attr f') ats'))
-> Attributes f ats -> f (Attributes f' ats')
unAttrs((Rec (Attr f) ats -> f (Rec (Attr f) ats))
-> Attributes f ats -> f (Attributes f ats))
-> ((Maybe (Apply f at) -> f (Maybe (Apply f at)))
-> Rec (Attr f) ats -> f (Rec (Attr f) ats))
-> (Maybe (Apply f at) -> f (Maybe (Apply f at)))
-> Attributes f ats
-> f (Attributes f ats)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(forall (r :: k1) (record :: (k1 -> *) -> [k1] -> *) (rs :: [k1])
(f :: k1 -> *) (g :: * -> *).
(RecElem record r r rs rs (RIndex r rs), RecElemFCtx record f,
Functor g) =>
(f r -> g (f r)) -> record f rs -> g (record f rs)
forall {k} (r :: k) (record :: (k -> *) -> [k] -> *) (rs :: [k])
(f :: k -> *) (g :: * -> *).
(RecElem record r r rs rs (RIndex r rs), RecElemFCtx record f,
Functor g) =>
(f r -> g (f r)) -> record f rs -> g (record f rs)
rlens @at)((Attr f at -> f (Attr f at))
-> Rec (Attr f) ats -> f (Rec (Attr f) ats))
-> ((Maybe (Apply f at) -> f (Maybe (Apply f at)))
-> Attr f at -> f (Attr f at))
-> (Maybe (Apply f at) -> f (Maybe (Apply f at)))
-> Rec (Attr f) ats
-> f (Rec (Attr f) ats)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Maybe (Apply f at) -> f (Maybe (Apply f at)))
-> Attr f at -> f (Attr f at)
forall u (f :: TyFun u (*) -> *) (label :: u) u
(f :: TyFun u (*) -> *) (label :: u) (p :: * -> * -> *)
(f :: * -> *).
(Profunctor p, Functor f) =>
p (Maybe (Apply f label)) (f (Maybe (Apply f label)))
-> p (Attr f label) (f (Attr f label))
getAttr
_Attr :: forall at ats proxy f. (at ∈ ats, RecApplicative ats)
=> proxy at -> Prism' (Attributes f ats) (Apply f at)
_Attr :: forall {k1} (at :: k1) (ats :: [k1]) (proxy :: k1 -> *)
(f :: TyFun k1 (*) -> *).
(at ∈ ats, RecApplicative ats) =>
proxy at -> Prism' (Attributes f ats) (Apply f at)
_Attr proxy at
a = (Apply f at -> Attributes f ats)
-> (Attributes f ats -> Maybe (Apply f at))
-> Prism
(Attributes f ats) (Attributes f ats) (Apply f at) (Apply f at)
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism' Apply f at -> Attributes f ats
setA Attributes f ats -> Maybe (Apply f at)
getA
where
setA :: Apply f at -> Attributes f ats
setA Apply f at
x = proxy at -> Apply f at -> Attributes f ats -> Attributes f ats
forall {u} (proxy :: u -> *) (at :: u) (ats :: [u]) (f :: u ~> *).
(at ∈ ats) =>
proxy at -> Apply f at -> Attributes f ats -> Attributes f ats
setAttr proxy at
a Apply f at
x Attributes f ats
forall a. Monoid a => a
mempty
getA :: Attributes f ats -> Maybe (Apply f at)
getA = proxy at -> Attributes f ats -> Maybe (Apply f at)
forall {k1} (at :: k1) (ats :: [k1]) (proxy :: k1 -> *)
(f :: TyFun k1 (*) -> *).
(at ∈ ats) =>
proxy at -> Attributes f ats -> Maybe (Apply f at)
lookupAttr proxy at
a
lookupAttr :: (at ∈ ats) => proxy at -> Attributes f ats -> Maybe (Apply f at)
lookupAttr :: forall {k1} (at :: k1) (ats :: [k1]) (proxy :: k1 -> *)
(f :: TyFun k1 (*) -> *).
(at ∈ ats) =>
proxy at -> Attributes f ats -> Maybe (Apply f at)
lookupAttr proxy at
p = Getting
(Maybe (Apply f at)) (Attributes f ats) (Maybe (Apply f at))
-> Attributes f ats -> Maybe (Apply f at)
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (proxy at -> Lens' (Attributes f ats) (Maybe (Apply f at))
forall {k1} (at :: k1) (ats :: [k1]) (proxy :: k1 -> *)
(f :: TyFun k1 (*) -> *).
(at ∈ ats) =>
proxy at -> Lens' (Attributes f ats) (Maybe (Apply f at))
ixAttr proxy at
p)
setAttr :: forall proxy at ats f. (at ∈ ats)
=> proxy at -> Apply f at -> Attributes f ats -> Attributes f ats
setAttr :: forall {u} (proxy :: u -> *) (at :: u) (ats :: [u]) (f :: u ~> *).
(at ∈ ats) =>
proxy at -> Apply f at -> Attributes f ats -> Attributes f ats
setAttr proxy at
_ Apply f at
a (Attrs Rec (Attr f) ats
r) = Rec (Attr f) ats -> Attributes f ats
forall u (f :: TyFun u (*) -> *) (ats :: [u]).
Rec (Attr f) ats -> Attributes f ats
Attrs (Rec (Attr f) ats -> Attributes f ats)
-> Rec (Attr f) ats -> Attributes f ats
forall a b. (a -> b) -> a -> b
$ Attr f at -> Rec (Attr f) ats -> Rec (Attr f) ats
forall k (r :: k) (rs :: [k]) (record :: (k -> *) -> [k] -> *)
(f :: k -> *).
(RecElem record r r rs rs (RIndex r rs), RecElemFCtx record f) =>
f r -> record f rs -> record f rs
rput (Apply f at -> Attr f at
forall {u} (f :: u ~> *) (label :: u).
Apply f label -> Attr f label
Attr Apply f at
a :: Attr f at) Rec (Attr f) ats
r
takeAttr :: forall proxy at ats f. (at ∈ ats)
=> proxy at -> Attributes f ats -> ( Maybe (Apply f at)
, Attributes f ats )
takeAttr :: forall {u} (proxy :: u -> *) (at :: u) (ats :: [u])
(f :: TyFun u (*) -> *).
(at ∈ ats) =>
proxy at
-> Attributes f ats -> (Maybe (Apply f at), Attributes f ats)
takeAttr proxy at
p Attributes f ats
ats = (proxy at -> Attributes f ats -> Maybe (Apply f at)
forall {k1} (at :: k1) (ats :: [k1]) (proxy :: k1 -> *)
(f :: TyFun k1 (*) -> *).
(at ∈ ats) =>
proxy at -> Attributes f ats -> Maybe (Apply f at)
lookupAttr proxy at
p Attributes f ats
ats, Attributes f ats
atsAttributes f ats
-> (Attributes f ats -> Attributes f ats) -> Attributes f ats
forall a b. a -> (a -> b) -> b
&proxy at -> Lens' (Attributes f ats) (Maybe (Apply f at))
forall {k1} (at :: k1) (ats :: [k1]) (proxy :: k1 -> *)
(f :: TyFun k1 (*) -> *).
(at ∈ ats) =>
proxy at -> Lens' (Attributes f ats) (Maybe (Apply f at))
ixAttr proxy at
p ((Maybe (Apply f at) -> Identity (Maybe (Apply f at)))
-> Attributes f ats -> Identity (Attributes f ats))
-> Maybe (Apply f at) -> Attributes f ats -> Attributes f ats
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Maybe (Apply f at)
forall a. Maybe a
Nothing)
unSetAttr :: forall proxy at ats f. (at ∈ ats)
=> proxy at -> Attributes f ats -> Attributes f ats
unSetAttr :: forall {u} (proxy :: u -> *) (at :: u) (ats :: [u])
(f :: TyFun u (*) -> *).
(at ∈ ats) =>
proxy at -> Attributes f ats -> Attributes f ats
unSetAttr proxy at
p = (Maybe (Apply f at), Attributes f ats) -> Attributes f ats
forall a b. (a, b) -> b
snd ((Maybe (Apply f at), Attributes f ats) -> Attributes f ats)
-> (Attributes f ats -> (Maybe (Apply f at), Attributes f ats))
-> Attributes f ats
-> Attributes f ats
forall b c a. (b -> c) -> (a -> b) -> a -> c
. proxy at
-> Attributes f ats -> (Maybe (Apply f at), Attributes f ats)
forall {u} (proxy :: u -> *) (at :: u) (ats :: [u])
(f :: TyFun u (*) -> *).
(at ∈ ats) =>
proxy at
-> Attributes f ats -> (Maybe (Apply f at), Attributes f ats)
takeAttr proxy at
p
attr :: (at ∈ ats, RecApplicative ats)
=> proxy at -> Apply f at -> Attributes f ats
attr :: forall {u} (at :: u) (ats :: [u]) (proxy :: u -> *) (f :: u ~> *).
(at ∈ ats, RecApplicative ats) =>
proxy at -> Apply f at -> Attributes f ats
attr proxy at
p Apply f at
x = Apply f at
xApply f at
-> Getting (Attributes f ats) (Apply f at) (Attributes f ats)
-> Attributes f ats
forall s a. s -> Getting a s a -> a
^.AReview (Attributes f ats) (Apply f at)
-> Getter (Apply f at) (Attributes f ats)
forall t b. AReview t b -> Getter b t
re (proxy at -> Prism' (Attributes f ats) (Apply f at)
forall {k1} (at :: k1) (ats :: [k1]) (proxy :: k1 -> *)
(f :: TyFun k1 (*) -> *).
(at ∈ ats, RecApplicative ats) =>
proxy at -> Prism' (Attributes f ats) (Apply f at)
_Attr proxy at
p)
data PinType = No | Yes | Horizontal | Vertical
deriving (PinType -> PinType -> Bool
(PinType -> PinType -> Bool)
-> (PinType -> PinType -> Bool) -> Eq PinType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PinType -> PinType -> Bool
== :: PinType -> PinType -> Bool
$c/= :: PinType -> PinType -> Bool
/= :: PinType -> PinType -> Bool
Eq,Int -> PinType -> ShowS
[PinType] -> ShowS
PinType -> String
(Int -> PinType -> ShowS)
-> (PinType -> String) -> ([PinType] -> ShowS) -> Show PinType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PinType -> ShowS
showsPrec :: Int -> PinType -> ShowS
$cshow :: PinType -> String
show :: PinType -> String
$cshowList :: [PinType] -> ShowS
showList :: [PinType] -> ShowS
Show,ReadPrec [PinType]
ReadPrec PinType
Int -> ReadS PinType
ReadS [PinType]
(Int -> ReadS PinType)
-> ReadS [PinType]
-> ReadPrec PinType
-> ReadPrec [PinType]
-> Read PinType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PinType
readsPrec :: Int -> ReadS PinType
$creadList :: ReadS [PinType]
readList :: ReadS [PinType]
$creadPrec :: ReadPrec PinType
readPrec :: ReadPrec PinType
$creadListPrec :: ReadPrec [PinType]
readListPrec :: ReadPrec [PinType]
Read,Int -> PinType
PinType -> Int
PinType -> [PinType]
PinType -> PinType
PinType -> PinType -> [PinType]
PinType -> PinType -> PinType -> [PinType]
(PinType -> PinType)
-> (PinType -> PinType)
-> (Int -> PinType)
-> (PinType -> Int)
-> (PinType -> [PinType])
-> (PinType -> PinType -> [PinType])
-> (PinType -> PinType -> [PinType])
-> (PinType -> PinType -> PinType -> [PinType])
-> Enum PinType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: PinType -> PinType
succ :: PinType -> PinType
$cpred :: PinType -> PinType
pred :: PinType -> PinType
$ctoEnum :: Int -> PinType
toEnum :: Int -> PinType
$cfromEnum :: PinType -> Int
fromEnum :: PinType -> Int
$cenumFrom :: PinType -> [PinType]
enumFrom :: PinType -> [PinType]
$cenumFromThen :: PinType -> PinType -> [PinType]
enumFromThen :: PinType -> PinType -> [PinType]
$cenumFromTo :: PinType -> PinType -> [PinType]
enumFromTo :: PinType -> PinType -> [PinType]
$cenumFromThenTo :: PinType -> PinType -> PinType -> [PinType]
enumFromThenTo :: PinType -> PinType -> PinType -> [PinType]
Enum)
data TransformationTypes = Affine | Rigid | Translations deriving (Int -> TransformationTypes -> ShowS
[TransformationTypes] -> ShowS
TransformationTypes -> String
(Int -> TransformationTypes -> ShowS)
-> (TransformationTypes -> String)
-> ([TransformationTypes] -> ShowS)
-> Show TransformationTypes
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TransformationTypes -> ShowS
showsPrec :: Int -> TransformationTypes -> ShowS
$cshow :: TransformationTypes -> String
show :: TransformationTypes -> String
$cshowList :: [TransformationTypes] -> ShowS
showList :: [TransformationTypes] -> ShowS
Show,ReadPrec [TransformationTypes]
ReadPrec TransformationTypes
Int -> ReadS TransformationTypes
ReadS [TransformationTypes]
(Int -> ReadS TransformationTypes)
-> ReadS [TransformationTypes]
-> ReadPrec TransformationTypes
-> ReadPrec [TransformationTypes]
-> Read TransformationTypes
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TransformationTypes
readsPrec :: Int -> ReadS TransformationTypes
$creadList :: ReadS [TransformationTypes]
readList :: ReadS [TransformationTypes]
$creadPrec :: ReadPrec TransformationTypes
readPrec :: ReadPrec TransformationTypes
$creadListPrec :: ReadPrec [TransformationTypes]
readListPrec :: ReadPrec [TransformationTypes]
Read,TransformationTypes -> TransformationTypes -> Bool
(TransformationTypes -> TransformationTypes -> Bool)
-> (TransformationTypes -> TransformationTypes -> Bool)
-> Eq TransformationTypes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TransformationTypes -> TransformationTypes -> Bool
== :: TransformationTypes -> TransformationTypes -> Bool
$c/= :: TransformationTypes -> TransformationTypes -> Bool
/= :: TransformationTypes -> TransformationTypes -> Bool
Eq,Int -> TransformationTypes
TransformationTypes -> Int
TransformationTypes -> [TransformationTypes]
TransformationTypes -> TransformationTypes
TransformationTypes -> TransformationTypes -> [TransformationTypes]
TransformationTypes
-> TransformationTypes
-> TransformationTypes
-> [TransformationTypes]
(TransformationTypes -> TransformationTypes)
-> (TransformationTypes -> TransformationTypes)
-> (Int -> TransformationTypes)
-> (TransformationTypes -> Int)
-> (TransformationTypes -> [TransformationTypes])
-> (TransformationTypes
-> TransformationTypes -> [TransformationTypes])
-> (TransformationTypes
-> TransformationTypes -> [TransformationTypes])
-> (TransformationTypes
-> TransformationTypes
-> TransformationTypes
-> [TransformationTypes])
-> Enum TransformationTypes
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: TransformationTypes -> TransformationTypes
succ :: TransformationTypes -> TransformationTypes
$cpred :: TransformationTypes -> TransformationTypes
pred :: TransformationTypes -> TransformationTypes
$ctoEnum :: Int -> TransformationTypes
toEnum :: Int -> TransformationTypes
$cfromEnum :: TransformationTypes -> Int
fromEnum :: TransformationTypes -> Int
$cenumFrom :: TransformationTypes -> [TransformationTypes]
enumFrom :: TransformationTypes -> [TransformationTypes]
$cenumFromThen :: TransformationTypes -> TransformationTypes -> [TransformationTypes]
enumFromThen :: TransformationTypes -> TransformationTypes -> [TransformationTypes]
$cenumFromTo :: TransformationTypes -> TransformationTypes -> [TransformationTypes]
enumFromTo :: TransformationTypes -> TransformationTypes -> [TransformationTypes]
$cenumFromThenTo :: TransformationTypes
-> TransformationTypes
-> TransformationTypes
-> [TransformationTypes]
enumFromThenTo :: TransformationTypes
-> TransformationTypes
-> TransformationTypes
-> [TransformationTypes]
Enum)
data HorizontalAlignment = AlignLeft | AlignHCenter | AlignRight
deriving (Int -> HorizontalAlignment -> ShowS
[HorizontalAlignment] -> ShowS
HorizontalAlignment -> String
(Int -> HorizontalAlignment -> ShowS)
-> (HorizontalAlignment -> String)
-> ([HorizontalAlignment] -> ShowS)
-> Show HorizontalAlignment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HorizontalAlignment -> ShowS
showsPrec :: Int -> HorizontalAlignment -> ShowS
$cshow :: HorizontalAlignment -> String
show :: HorizontalAlignment -> String
$cshowList :: [HorizontalAlignment] -> ShowS
showList :: [HorizontalAlignment] -> ShowS
Show,ReadPrec [HorizontalAlignment]
ReadPrec HorizontalAlignment
Int -> ReadS HorizontalAlignment
ReadS [HorizontalAlignment]
(Int -> ReadS HorizontalAlignment)
-> ReadS [HorizontalAlignment]
-> ReadPrec HorizontalAlignment
-> ReadPrec [HorizontalAlignment]
-> Read HorizontalAlignment
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS HorizontalAlignment
readsPrec :: Int -> ReadS HorizontalAlignment
$creadList :: ReadS [HorizontalAlignment]
readList :: ReadS [HorizontalAlignment]
$creadPrec :: ReadPrec HorizontalAlignment
readPrec :: ReadPrec HorizontalAlignment
$creadListPrec :: ReadPrec [HorizontalAlignment]
readListPrec :: ReadPrec [HorizontalAlignment]
Read,HorizontalAlignment -> HorizontalAlignment -> Bool
(HorizontalAlignment -> HorizontalAlignment -> Bool)
-> (HorizontalAlignment -> HorizontalAlignment -> Bool)
-> Eq HorizontalAlignment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HorizontalAlignment -> HorizontalAlignment -> Bool
== :: HorizontalAlignment -> HorizontalAlignment -> Bool
$c/= :: HorizontalAlignment -> HorizontalAlignment -> Bool
/= :: HorizontalAlignment -> HorizontalAlignment -> Bool
Eq,Eq HorizontalAlignment
Eq HorizontalAlignment =>
(HorizontalAlignment -> HorizontalAlignment -> Ordering)
-> (HorizontalAlignment -> HorizontalAlignment -> Bool)
-> (HorizontalAlignment -> HorizontalAlignment -> Bool)
-> (HorizontalAlignment -> HorizontalAlignment -> Bool)
-> (HorizontalAlignment -> HorizontalAlignment -> Bool)
-> (HorizontalAlignment
-> HorizontalAlignment -> HorizontalAlignment)
-> (HorizontalAlignment
-> HorizontalAlignment -> HorizontalAlignment)
-> Ord HorizontalAlignment
HorizontalAlignment -> HorizontalAlignment -> Bool
HorizontalAlignment -> HorizontalAlignment -> Ordering
HorizontalAlignment -> HorizontalAlignment -> HorizontalAlignment
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: HorizontalAlignment -> HorizontalAlignment -> Ordering
compare :: HorizontalAlignment -> HorizontalAlignment -> Ordering
$c< :: HorizontalAlignment -> HorizontalAlignment -> Bool
< :: HorizontalAlignment -> HorizontalAlignment -> Bool
$c<= :: HorizontalAlignment -> HorizontalAlignment -> Bool
<= :: HorizontalAlignment -> HorizontalAlignment -> Bool
$c> :: HorizontalAlignment -> HorizontalAlignment -> Bool
> :: HorizontalAlignment -> HorizontalAlignment -> Bool
$c>= :: HorizontalAlignment -> HorizontalAlignment -> Bool
>= :: HorizontalAlignment -> HorizontalAlignment -> Bool
$cmax :: HorizontalAlignment -> HorizontalAlignment -> HorizontalAlignment
max :: HorizontalAlignment -> HorizontalAlignment -> HorizontalAlignment
$cmin :: HorizontalAlignment -> HorizontalAlignment -> HorizontalAlignment
min :: HorizontalAlignment -> HorizontalAlignment -> HorizontalAlignment
Ord,Int -> HorizontalAlignment
HorizontalAlignment -> Int
HorizontalAlignment -> [HorizontalAlignment]
HorizontalAlignment -> HorizontalAlignment
HorizontalAlignment -> HorizontalAlignment -> [HorizontalAlignment]
HorizontalAlignment
-> HorizontalAlignment
-> HorizontalAlignment
-> [HorizontalAlignment]
(HorizontalAlignment -> HorizontalAlignment)
-> (HorizontalAlignment -> HorizontalAlignment)
-> (Int -> HorizontalAlignment)
-> (HorizontalAlignment -> Int)
-> (HorizontalAlignment -> [HorizontalAlignment])
-> (HorizontalAlignment
-> HorizontalAlignment -> [HorizontalAlignment])
-> (HorizontalAlignment
-> HorizontalAlignment -> [HorizontalAlignment])
-> (HorizontalAlignment
-> HorizontalAlignment
-> HorizontalAlignment
-> [HorizontalAlignment])
-> Enum HorizontalAlignment
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: HorizontalAlignment -> HorizontalAlignment
succ :: HorizontalAlignment -> HorizontalAlignment
$cpred :: HorizontalAlignment -> HorizontalAlignment
pred :: HorizontalAlignment -> HorizontalAlignment
$ctoEnum :: Int -> HorizontalAlignment
toEnum :: Int -> HorizontalAlignment
$cfromEnum :: HorizontalAlignment -> Int
fromEnum :: HorizontalAlignment -> Int
$cenumFrom :: HorizontalAlignment -> [HorizontalAlignment]
enumFrom :: HorizontalAlignment -> [HorizontalAlignment]
$cenumFromThen :: HorizontalAlignment -> HorizontalAlignment -> [HorizontalAlignment]
enumFromThen :: HorizontalAlignment -> HorizontalAlignment -> [HorizontalAlignment]
$cenumFromTo :: HorizontalAlignment -> HorizontalAlignment -> [HorizontalAlignment]
enumFromTo :: HorizontalAlignment -> HorizontalAlignment -> [HorizontalAlignment]
$cenumFromThenTo :: HorizontalAlignment
-> HorizontalAlignment
-> HorizontalAlignment
-> [HorizontalAlignment]
enumFromThenTo :: HorizontalAlignment
-> HorizontalAlignment
-> HorizontalAlignment
-> [HorizontalAlignment]
Enum)
data VerticalAlignment = AlignTop | AlignVCenter | AlignBottom | AlignBaseline
deriving (Int -> VerticalAlignment -> ShowS
[VerticalAlignment] -> ShowS
VerticalAlignment -> String
(Int -> VerticalAlignment -> ShowS)
-> (VerticalAlignment -> String)
-> ([VerticalAlignment] -> ShowS)
-> Show VerticalAlignment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VerticalAlignment -> ShowS
showsPrec :: Int -> VerticalAlignment -> ShowS
$cshow :: VerticalAlignment -> String
show :: VerticalAlignment -> String
$cshowList :: [VerticalAlignment] -> ShowS
showList :: [VerticalAlignment] -> ShowS
Show,ReadPrec [VerticalAlignment]
ReadPrec VerticalAlignment
Int -> ReadS VerticalAlignment
ReadS [VerticalAlignment]
(Int -> ReadS VerticalAlignment)
-> ReadS [VerticalAlignment]
-> ReadPrec VerticalAlignment
-> ReadPrec [VerticalAlignment]
-> Read VerticalAlignment
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS VerticalAlignment
readsPrec :: Int -> ReadS VerticalAlignment
$creadList :: ReadS [VerticalAlignment]
readList :: ReadS [VerticalAlignment]
$creadPrec :: ReadPrec VerticalAlignment
readPrec :: ReadPrec VerticalAlignment
$creadListPrec :: ReadPrec [VerticalAlignment]
readListPrec :: ReadPrec [VerticalAlignment]
Read,VerticalAlignment -> VerticalAlignment -> Bool
(VerticalAlignment -> VerticalAlignment -> Bool)
-> (VerticalAlignment -> VerticalAlignment -> Bool)
-> Eq VerticalAlignment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VerticalAlignment -> VerticalAlignment -> Bool
== :: VerticalAlignment -> VerticalAlignment -> Bool
$c/= :: VerticalAlignment -> VerticalAlignment -> Bool
/= :: VerticalAlignment -> VerticalAlignment -> Bool
Eq,Eq VerticalAlignment
Eq VerticalAlignment =>
(VerticalAlignment -> VerticalAlignment -> Ordering)
-> (VerticalAlignment -> VerticalAlignment -> Bool)
-> (VerticalAlignment -> VerticalAlignment -> Bool)
-> (VerticalAlignment -> VerticalAlignment -> Bool)
-> (VerticalAlignment -> VerticalAlignment -> Bool)
-> (VerticalAlignment -> VerticalAlignment -> VerticalAlignment)
-> (VerticalAlignment -> VerticalAlignment -> VerticalAlignment)
-> Ord VerticalAlignment
VerticalAlignment -> VerticalAlignment -> Bool
VerticalAlignment -> VerticalAlignment -> Ordering
VerticalAlignment -> VerticalAlignment -> VerticalAlignment
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: VerticalAlignment -> VerticalAlignment -> Ordering
compare :: VerticalAlignment -> VerticalAlignment -> Ordering
$c< :: VerticalAlignment -> VerticalAlignment -> Bool
< :: VerticalAlignment -> VerticalAlignment -> Bool
$c<= :: VerticalAlignment -> VerticalAlignment -> Bool
<= :: VerticalAlignment -> VerticalAlignment -> Bool
$c> :: VerticalAlignment -> VerticalAlignment -> Bool
> :: VerticalAlignment -> VerticalAlignment -> Bool
$c>= :: VerticalAlignment -> VerticalAlignment -> Bool
>= :: VerticalAlignment -> VerticalAlignment -> Bool
$cmax :: VerticalAlignment -> VerticalAlignment -> VerticalAlignment
max :: VerticalAlignment -> VerticalAlignment -> VerticalAlignment
$cmin :: VerticalAlignment -> VerticalAlignment -> VerticalAlignment
min :: VerticalAlignment -> VerticalAlignment -> VerticalAlignment
Ord,Int -> VerticalAlignment
VerticalAlignment -> Int
VerticalAlignment -> [VerticalAlignment]
VerticalAlignment -> VerticalAlignment
VerticalAlignment -> VerticalAlignment -> [VerticalAlignment]
VerticalAlignment
-> VerticalAlignment -> VerticalAlignment -> [VerticalAlignment]
(VerticalAlignment -> VerticalAlignment)
-> (VerticalAlignment -> VerticalAlignment)
-> (Int -> VerticalAlignment)
-> (VerticalAlignment -> Int)
-> (VerticalAlignment -> [VerticalAlignment])
-> (VerticalAlignment -> VerticalAlignment -> [VerticalAlignment])
-> (VerticalAlignment -> VerticalAlignment -> [VerticalAlignment])
-> (VerticalAlignment
-> VerticalAlignment -> VerticalAlignment -> [VerticalAlignment])
-> Enum VerticalAlignment
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: VerticalAlignment -> VerticalAlignment
succ :: VerticalAlignment -> VerticalAlignment
$cpred :: VerticalAlignment -> VerticalAlignment
pred :: VerticalAlignment -> VerticalAlignment
$ctoEnum :: Int -> VerticalAlignment
toEnum :: Int -> VerticalAlignment
$cfromEnum :: VerticalAlignment -> Int
fromEnum :: VerticalAlignment -> Int
$cenumFrom :: VerticalAlignment -> [VerticalAlignment]
enumFrom :: VerticalAlignment -> [VerticalAlignment]
$cenumFromThen :: VerticalAlignment -> VerticalAlignment -> [VerticalAlignment]
enumFromThen :: VerticalAlignment -> VerticalAlignment -> [VerticalAlignment]
$cenumFromTo :: VerticalAlignment -> VerticalAlignment -> [VerticalAlignment]
enumFromTo :: VerticalAlignment -> VerticalAlignment -> [VerticalAlignment]
$cenumFromThenTo :: VerticalAlignment
-> VerticalAlignment -> VerticalAlignment -> [VerticalAlignment]
enumFromThenTo :: VerticalAlignment
-> VerticalAlignment -> VerticalAlignment -> [VerticalAlignment]
Enum)
type TeXStyle = Text
type TextSizeUnit r = r
newtype IpeSize r = IpeSize (IpeValue r) deriving (Int -> IpeSize r -> ShowS
[IpeSize r] -> ShowS
IpeSize r -> String
(Int -> IpeSize r -> ShowS)
-> (IpeSize r -> String)
-> ([IpeSize r] -> ShowS)
-> Show (IpeSize r)
forall r. Show r => Int -> IpeSize r -> ShowS
forall r. Show r => [IpeSize r] -> ShowS
forall r. Show r => IpeSize r -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall r. Show r => Int -> IpeSize r -> ShowS
showsPrec :: Int -> IpeSize r -> ShowS
$cshow :: forall r. Show r => IpeSize r -> String
show :: IpeSize r -> String
$cshowList :: forall r. Show r => [IpeSize r] -> ShowS
showList :: [IpeSize r] -> ShowS
Show,IpeSize r -> IpeSize r -> Bool
(IpeSize r -> IpeSize r -> Bool)
-> (IpeSize r -> IpeSize r -> Bool) -> Eq (IpeSize r)
forall r. Eq r => IpeSize r -> IpeSize r -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall r. Eq r => IpeSize r -> IpeSize r -> Bool
== :: IpeSize r -> IpeSize r -> Bool
$c/= :: forall r. Eq r => IpeSize r -> IpeSize r -> Bool
/= :: IpeSize r -> IpeSize r -> Bool
Eq,Eq (IpeSize r)
Eq (IpeSize r) =>
(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)
-> (IpeSize r -> IpeSize r -> IpeSize r)
-> (IpeSize r -> IpeSize r -> IpeSize r)
-> Ord (IpeSize r)
IpeSize r -> IpeSize r -> Bool
IpeSize r -> IpeSize r -> Ordering
IpeSize r -> IpeSize r -> IpeSize r
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall r. Ord r => Eq (IpeSize r)
forall r. Ord r => IpeSize r -> IpeSize r -> Bool
forall r. Ord r => IpeSize r -> IpeSize r -> Ordering
forall r. Ord r => IpeSize r -> IpeSize r -> IpeSize r
$ccompare :: forall r. Ord r => IpeSize r -> IpeSize r -> Ordering
compare :: IpeSize r -> IpeSize r -> Ordering
$c< :: forall r. Ord r => IpeSize r -> IpeSize r -> Bool
< :: IpeSize r -> IpeSize r -> Bool
$c<= :: forall r. Ord r => IpeSize r -> IpeSize r -> Bool
<= :: IpeSize r -> IpeSize r -> Bool
$c> :: forall r. Ord r => IpeSize r -> IpeSize r -> Bool
> :: IpeSize r -> IpeSize r -> Bool
$c>= :: forall r. Ord r => IpeSize r -> IpeSize r -> Bool
>= :: IpeSize r -> IpeSize r -> Bool
$cmax :: forall r. Ord r => IpeSize r -> IpeSize r -> IpeSize r
max :: IpeSize r -> IpeSize r -> IpeSize r
$cmin :: forall r. Ord r => IpeSize r -> IpeSize r -> IpeSize r
min :: IpeSize r -> IpeSize r -> IpeSize r
Ord,(forall a b. (a -> b) -> IpeSize a -> IpeSize b)
-> (forall a b. a -> IpeSize b -> IpeSize a) -> Functor IpeSize
forall a b. a -> IpeSize b -> IpeSize a
forall a b. (a -> b) -> IpeSize a -> IpeSize b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> IpeSize a -> IpeSize b
fmap :: forall a b. (a -> b) -> IpeSize a -> IpeSize b
$c<$ :: forall a b. a -> IpeSize b -> IpeSize a
<$ :: forall a b. a -> IpeSize b -> IpeSize a
Functor,(forall m. Monoid m => IpeSize m -> m)
-> (forall m a. Monoid m => (a -> m) -> IpeSize a -> m)
-> (forall m a. Monoid m => (a -> m) -> IpeSize a -> m)
-> (forall a b. (a -> b -> b) -> b -> IpeSize a -> b)
-> (forall a b. (a -> b -> b) -> b -> IpeSize a -> b)
-> (forall b a. (b -> a -> b) -> b -> IpeSize a -> b)
-> (forall b a. (b -> a -> b) -> b -> IpeSize a -> b)
-> (forall a. (a -> a -> a) -> IpeSize a -> a)
-> (forall a. (a -> a -> a) -> IpeSize a -> a)
-> (forall a. IpeSize a -> [a])
-> (forall a. IpeSize a -> Bool)
-> (forall a. IpeSize a -> Int)
-> (forall a. Eq a => a -> IpeSize a -> Bool)
-> (forall a. Ord a => IpeSize a -> a)
-> (forall a. Ord a => IpeSize a -> a)
-> (forall a. Num a => IpeSize a -> a)
-> (forall a. Num a => IpeSize a -> a)
-> Foldable IpeSize
forall a. Eq a => a -> IpeSize a -> Bool
forall a. Num a => IpeSize a -> a
forall a. Ord a => IpeSize a -> a
forall m. Monoid m => IpeSize m -> m
forall a. IpeSize a -> Bool
forall a. IpeSize a -> Int
forall a. IpeSize a -> [a]
forall a. (a -> a -> a) -> IpeSize a -> a
forall m a. Monoid m => (a -> m) -> IpeSize a -> m
forall b a. (b -> a -> b) -> b -> IpeSize a -> b
forall a b. (a -> b -> b) -> b -> IpeSize a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => IpeSize m -> m
fold :: forall m. Monoid m => IpeSize m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> IpeSize a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> IpeSize a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> IpeSize a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> IpeSize a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> IpeSize a -> b
foldr :: forall a b. (a -> b -> b) -> b -> IpeSize a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> IpeSize a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> IpeSize a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> IpeSize a -> b
foldl :: forall b a. (b -> a -> b) -> b -> IpeSize a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> IpeSize a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> IpeSize a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> IpeSize a -> a
foldr1 :: forall a. (a -> a -> a) -> IpeSize a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> IpeSize a -> a
foldl1 :: forall a. (a -> a -> a) -> IpeSize a -> a
$ctoList :: forall a. IpeSize a -> [a]
toList :: forall a. IpeSize a -> [a]
$cnull :: forall a. IpeSize a -> Bool
null :: forall a. IpeSize a -> Bool
$clength :: forall a. IpeSize a -> Int
length :: forall a. IpeSize a -> Int
$celem :: forall a. Eq a => a -> IpeSize a -> Bool
elem :: forall a. Eq a => a -> IpeSize a -> Bool
$cmaximum :: forall a. Ord a => IpeSize a -> a
maximum :: forall a. Ord a => IpeSize a -> a
$cminimum :: forall a. Ord a => IpeSize a -> a
minimum :: forall a. Ord a => IpeSize a -> a
$csum :: forall a. Num a => IpeSize a -> a
sum :: forall a. Num a => IpeSize a -> a
$cproduct :: forall a. Num a => IpeSize a -> a
product :: forall a. Num a => IpeSize a -> a
Foldable,Functor IpeSize
Foldable IpeSize
(Functor IpeSize, Foldable IpeSize) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IpeSize a -> f (IpeSize b))
-> (forall (f :: * -> *) a.
Applicative f =>
IpeSize (f a) -> f (IpeSize a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IpeSize a -> m (IpeSize b))
-> (forall (m :: * -> *) a.
Monad m =>
IpeSize (m a) -> m (IpeSize a))
-> Traversable IpeSize
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => IpeSize (m a) -> m (IpeSize a)
forall (f :: * -> *) a.
Applicative f =>
IpeSize (f a) -> f (IpeSize a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IpeSize a -> m (IpeSize b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IpeSize a -> f (IpeSize b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IpeSize a -> f (IpeSize b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IpeSize a -> f (IpeSize b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
IpeSize (f a) -> f (IpeSize a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
IpeSize (f a) -> f (IpeSize a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IpeSize a -> m (IpeSize b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IpeSize a -> m (IpeSize b)
$csequence :: forall (m :: * -> *) a. Monad m => IpeSize (m a) -> m (IpeSize a)
sequence :: forall (m :: * -> *) a. Monad m => IpeSize (m a) -> m (IpeSize a)
Traversable)
newtype IpePen r = IpePen (IpeValue r) deriving (Int -> IpePen r -> ShowS
[IpePen r] -> ShowS
IpePen r -> String
(Int -> IpePen r -> ShowS)
-> (IpePen r -> String) -> ([IpePen r] -> ShowS) -> Show (IpePen r)
forall r. Show r => Int -> IpePen r -> ShowS
forall r. Show r => [IpePen r] -> ShowS
forall r. Show r => IpePen r -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall r. Show r => Int -> IpePen r -> ShowS
showsPrec :: Int -> IpePen r -> ShowS
$cshow :: forall r. Show r => IpePen r -> String
show :: IpePen r -> String
$cshowList :: forall r. Show r => [IpePen r] -> ShowS
showList :: [IpePen r] -> ShowS
Show,IpePen r -> IpePen r -> Bool
(IpePen r -> IpePen r -> Bool)
-> (IpePen r -> IpePen r -> Bool) -> Eq (IpePen r)
forall r. Eq r => IpePen r -> IpePen r -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall r. Eq r => IpePen r -> IpePen r -> Bool
== :: IpePen r -> IpePen r -> Bool
$c/= :: forall r. Eq r => IpePen r -> IpePen r -> Bool
/= :: IpePen r -> IpePen r -> Bool
Eq,Eq (IpePen r)
Eq (IpePen r) =>
(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)
-> (IpePen r -> IpePen r -> IpePen r)
-> (IpePen r -> IpePen r -> IpePen r)
-> Ord (IpePen r)
IpePen r -> IpePen r -> Bool
IpePen r -> IpePen r -> Ordering
IpePen r -> IpePen r -> IpePen r
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall r. Ord r => Eq (IpePen r)
forall r. Ord r => IpePen r -> IpePen r -> Bool
forall r. Ord r => IpePen r -> IpePen r -> Ordering
forall r. Ord r => IpePen r -> IpePen r -> IpePen r
$ccompare :: forall r. Ord r => IpePen r -> IpePen r -> Ordering
compare :: IpePen r -> IpePen r -> Ordering
$c< :: forall r. Ord r => IpePen r -> IpePen r -> Bool
< :: IpePen r -> IpePen r -> Bool
$c<= :: forall r. Ord r => IpePen r -> IpePen r -> Bool
<= :: IpePen r -> IpePen r -> Bool
$c> :: forall r. Ord r => IpePen r -> IpePen r -> Bool
> :: IpePen r -> IpePen r -> Bool
$c>= :: forall r. Ord r => IpePen r -> IpePen r -> Bool
>= :: IpePen r -> IpePen r -> Bool
$cmax :: forall r. Ord r => IpePen r -> IpePen r -> IpePen r
max :: IpePen r -> IpePen r -> IpePen r
$cmin :: forall r. Ord r => IpePen r -> IpePen r -> IpePen r
min :: IpePen r -> IpePen r -> IpePen r
Ord,(forall a b. (a -> b) -> IpePen a -> IpePen b)
-> (forall a b. a -> IpePen b -> IpePen a) -> Functor IpePen
forall a b. a -> IpePen b -> IpePen a
forall a b. (a -> b) -> IpePen a -> IpePen b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> IpePen a -> IpePen b
fmap :: forall a b. (a -> b) -> IpePen a -> IpePen b
$c<$ :: forall a b. a -> IpePen b -> IpePen a
<$ :: forall a b. a -> IpePen b -> IpePen a
Functor,(forall m. Monoid m => IpePen m -> m)
-> (forall m a. Monoid m => (a -> m) -> IpePen a -> m)
-> (forall m a. Monoid m => (a -> m) -> IpePen a -> m)
-> (forall a b. (a -> b -> b) -> b -> IpePen a -> b)
-> (forall a b. (a -> b -> b) -> b -> IpePen a -> b)
-> (forall b a. (b -> a -> b) -> b -> IpePen a -> b)
-> (forall b a. (b -> a -> b) -> b -> IpePen a -> b)
-> (forall a. (a -> a -> a) -> IpePen a -> a)
-> (forall a. (a -> a -> a) -> IpePen a -> a)
-> (forall a. IpePen a -> [a])
-> (forall a. IpePen a -> Bool)
-> (forall a. IpePen a -> Int)
-> (forall a. Eq a => a -> IpePen a -> Bool)
-> (forall a. Ord a => IpePen a -> a)
-> (forall a. Ord a => IpePen a -> a)
-> (forall a. Num a => IpePen a -> a)
-> (forall a. Num a => IpePen a -> a)
-> Foldable IpePen
forall a. Eq a => a -> IpePen a -> Bool
forall a. Num a => IpePen a -> a
forall a. Ord a => IpePen a -> a
forall m. Monoid m => IpePen m -> m
forall a. IpePen a -> Bool
forall a. IpePen a -> Int
forall a. IpePen a -> [a]
forall a. (a -> a -> a) -> IpePen a -> a
forall m a. Monoid m => (a -> m) -> IpePen a -> m
forall b a. (b -> a -> b) -> b -> IpePen a -> b
forall a b. (a -> b -> b) -> b -> IpePen a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => IpePen m -> m
fold :: forall m. Monoid m => IpePen m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> IpePen a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> IpePen a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> IpePen a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> IpePen a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> IpePen a -> b
foldr :: forall a b. (a -> b -> b) -> b -> IpePen a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> IpePen a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> IpePen a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> IpePen a -> b
foldl :: forall b a. (b -> a -> b) -> b -> IpePen a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> IpePen a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> IpePen a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> IpePen a -> a
foldr1 :: forall a. (a -> a -> a) -> IpePen a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> IpePen a -> a
foldl1 :: forall a. (a -> a -> a) -> IpePen a -> a
$ctoList :: forall a. IpePen a -> [a]
toList :: forall a. IpePen a -> [a]
$cnull :: forall a. IpePen a -> Bool
null :: forall a. IpePen a -> Bool
$clength :: forall a. IpePen a -> Int
length :: forall a. IpePen a -> Int
$celem :: forall a. Eq a => a -> IpePen a -> Bool
elem :: forall a. Eq a => a -> IpePen a -> Bool
$cmaximum :: forall a. Ord a => IpePen a -> a
maximum :: forall a. Ord a => IpePen a -> a
$cminimum :: forall a. Ord a => IpePen a -> a
minimum :: forall a. Ord a => IpePen a -> a
$csum :: forall a. Num a => IpePen a -> a
sum :: forall a. Num a => IpePen a -> a
$cproduct :: forall a. Num a => IpePen a -> a
product :: forall a. Num a => IpePen a -> a
Foldable,Functor IpePen
Foldable IpePen
(Functor IpePen, Foldable IpePen) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IpePen a -> f (IpePen b))
-> (forall (f :: * -> *) a.
Applicative f =>
IpePen (f a) -> f (IpePen a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IpePen a -> m (IpePen b))
-> (forall (m :: * -> *) a.
Monad m =>
IpePen (m a) -> m (IpePen a))
-> Traversable IpePen
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => IpePen (m a) -> m (IpePen a)
forall (f :: * -> *) a.
Applicative f =>
IpePen (f a) -> f (IpePen a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IpePen a -> m (IpePen b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IpePen a -> f (IpePen b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IpePen a -> f (IpePen b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IpePen a -> f (IpePen b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
IpePen (f a) -> f (IpePen a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
IpePen (f a) -> f (IpePen a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IpePen a -> m (IpePen b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IpePen a -> m (IpePen b)
$csequence :: forall (m :: * -> *) a. Monad m => IpePen (m a) -> m (IpePen a)
sequence :: forall (m :: * -> *) a. Monad m => IpePen (m a) -> m (IpePen a)
Traversable)
data IpeDash r = DashNamed Text
| DashPattern [r] r
deriving (Int -> IpeDash r -> ShowS
[IpeDash r] -> ShowS
IpeDash r -> String
(Int -> IpeDash r -> ShowS)
-> (IpeDash r -> String)
-> ([IpeDash r] -> ShowS)
-> Show (IpeDash r)
forall r. Show r => Int -> IpeDash r -> ShowS
forall r. Show r => [IpeDash r] -> ShowS
forall r. Show r => IpeDash r -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall r. Show r => Int -> IpeDash r -> ShowS
showsPrec :: Int -> IpeDash r -> ShowS
$cshow :: forall r. Show r => IpeDash r -> String
show :: IpeDash r -> String
$cshowList :: forall r. Show r => [IpeDash r] -> ShowS
showList :: [IpeDash r] -> ShowS
Show,IpeDash r -> IpeDash r -> Bool
(IpeDash r -> IpeDash r -> Bool)
-> (IpeDash r -> IpeDash r -> Bool) -> Eq (IpeDash r)
forall r. Eq r => IpeDash r -> IpeDash r -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall r. Eq r => IpeDash r -> IpeDash r -> Bool
== :: IpeDash r -> IpeDash r -> Bool
$c/= :: forall r. Eq r => IpeDash r -> IpeDash r -> Bool
/= :: IpeDash r -> IpeDash r -> Bool
Eq,(forall a b. (a -> b) -> IpeDash a -> IpeDash b)
-> (forall a b. a -> IpeDash b -> IpeDash a) -> Functor IpeDash
forall a b. a -> IpeDash b -> IpeDash a
forall a b. (a -> b) -> IpeDash a -> IpeDash b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> IpeDash a -> IpeDash b
fmap :: forall a b. (a -> b) -> IpeDash a -> IpeDash b
$c<$ :: forall a b. a -> IpeDash b -> IpeDash a
<$ :: forall a b. a -> IpeDash b -> IpeDash a
Functor,(forall m. Monoid m => IpeDash m -> m)
-> (forall m a. Monoid m => (a -> m) -> IpeDash a -> m)
-> (forall m a. Monoid m => (a -> m) -> IpeDash a -> m)
-> (forall a b. (a -> b -> b) -> b -> IpeDash a -> b)
-> (forall a b. (a -> b -> b) -> b -> IpeDash a -> b)
-> (forall b a. (b -> a -> b) -> b -> IpeDash a -> b)
-> (forall b a. (b -> a -> b) -> b -> IpeDash a -> b)
-> (forall a. (a -> a -> a) -> IpeDash a -> a)
-> (forall a. (a -> a -> a) -> IpeDash a -> a)
-> (forall a. IpeDash a -> [a])
-> (forall a. IpeDash a -> Bool)
-> (forall a. IpeDash a -> Int)
-> (forall a. Eq a => a -> IpeDash a -> Bool)
-> (forall a. Ord a => IpeDash a -> a)
-> (forall a. Ord a => IpeDash a -> a)
-> (forall a. Num a => IpeDash a -> a)
-> (forall a. Num a => IpeDash a -> a)
-> Foldable IpeDash
forall a. Eq a => a -> IpeDash a -> Bool
forall a. Num a => IpeDash a -> a
forall a. Ord a => IpeDash a -> a
forall m. Monoid m => IpeDash m -> m
forall a. IpeDash a -> Bool
forall a. IpeDash a -> Int
forall a. IpeDash a -> [a]
forall a. (a -> a -> a) -> IpeDash a -> a
forall m a. Monoid m => (a -> m) -> IpeDash a -> m
forall b a. (b -> a -> b) -> b -> IpeDash a -> b
forall a b. (a -> b -> b) -> b -> IpeDash a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => IpeDash m -> m
fold :: forall m. Monoid m => IpeDash m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> IpeDash a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> IpeDash a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> IpeDash a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> IpeDash a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> IpeDash a -> b
foldr :: forall a b. (a -> b -> b) -> b -> IpeDash a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> IpeDash a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> IpeDash a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> IpeDash a -> b
foldl :: forall b a. (b -> a -> b) -> b -> IpeDash a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> IpeDash a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> IpeDash a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> IpeDash a -> a
foldr1 :: forall a. (a -> a -> a) -> IpeDash a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> IpeDash a -> a
foldl1 :: forall a. (a -> a -> a) -> IpeDash a -> a
$ctoList :: forall a. IpeDash a -> [a]
toList :: forall a. IpeDash a -> [a]
$cnull :: forall a. IpeDash a -> Bool
null :: forall a. IpeDash a -> Bool
$clength :: forall a. IpeDash a -> Int
length :: forall a. IpeDash a -> Int
$celem :: forall a. Eq a => a -> IpeDash a -> Bool
elem :: forall a. Eq a => a -> IpeDash a -> Bool
$cmaximum :: forall a. Ord a => IpeDash a -> a
maximum :: forall a. Ord a => IpeDash a -> a
$cminimum :: forall a. Ord a => IpeDash a -> a
minimum :: forall a. Ord a => IpeDash a -> a
$csum :: forall a. Num a => IpeDash a -> a
sum :: forall a. Num a => IpeDash a -> a
$cproduct :: forall a. Num a => IpeDash a -> a
product :: forall a. Num a => IpeDash a -> a
Foldable,Functor IpeDash
Foldable IpeDash
(Functor IpeDash, Foldable IpeDash) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IpeDash a -> f (IpeDash b))
-> (forall (f :: * -> *) a.
Applicative f =>
IpeDash (f a) -> f (IpeDash a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IpeDash a -> m (IpeDash b))
-> (forall (m :: * -> *) a.
Monad m =>
IpeDash (m a) -> m (IpeDash a))
-> Traversable IpeDash
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => IpeDash (m a) -> m (IpeDash a)
forall (f :: * -> *) a.
Applicative f =>
IpeDash (f a) -> f (IpeDash a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IpeDash a -> m (IpeDash b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IpeDash a -> f (IpeDash b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IpeDash a -> f (IpeDash b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IpeDash a -> f (IpeDash b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
IpeDash (f a) -> f (IpeDash a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
IpeDash (f a) -> f (IpeDash a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IpeDash a -> m (IpeDash b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IpeDash a -> m (IpeDash b)
$csequence :: forall (m :: * -> *) a. Monad m => IpeDash (m a) -> m (IpeDash a)
sequence :: forall (m :: * -> *) a. Monad m => IpeDash (m a) -> m (IpeDash a)
Traversable)
data FillType = Wind | EOFill deriving (Int -> FillType -> ShowS
[FillType] -> ShowS
FillType -> String
(Int -> FillType -> ShowS)
-> (FillType -> String) -> ([FillType] -> ShowS) -> Show FillType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FillType -> ShowS
showsPrec :: Int -> FillType -> ShowS
$cshow :: FillType -> String
show :: FillType -> String
$cshowList :: [FillType] -> ShowS
showList :: [FillType] -> ShowS
Show,ReadPrec [FillType]
ReadPrec FillType
Int -> ReadS FillType
ReadS [FillType]
(Int -> ReadS FillType)
-> ReadS [FillType]
-> ReadPrec FillType
-> ReadPrec [FillType]
-> Read FillType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FillType
readsPrec :: Int -> ReadS FillType
$creadList :: ReadS [FillType]
readList :: ReadS [FillType]
$creadPrec :: ReadPrec FillType
readPrec :: ReadPrec FillType
$creadListPrec :: ReadPrec [FillType]
readListPrec :: ReadPrec [FillType]
Read,FillType -> FillType -> Bool
(FillType -> FillType -> Bool)
-> (FillType -> FillType -> Bool) -> Eq FillType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FillType -> FillType -> Bool
== :: FillType -> FillType -> Bool
$c/= :: FillType -> FillType -> Bool
/= :: FillType -> FillType -> Bool
Eq)
type IpeOpacity = Text
type IpeTiling = Text
type IpeGradient = Text
data IpeArrow r = IpeArrow { forall r. IpeArrow r -> Text
_arrowName :: Text
, forall r. IpeArrow r -> IpeSize r
_arrowSize :: IpeSize r
} deriving (Int -> IpeArrow r -> ShowS
[IpeArrow r] -> ShowS
IpeArrow r -> String
(Int -> IpeArrow r -> ShowS)
-> (IpeArrow r -> String)
-> ([IpeArrow r] -> ShowS)
-> Show (IpeArrow r)
forall r. Show r => Int -> IpeArrow r -> ShowS
forall r. Show r => [IpeArrow r] -> ShowS
forall r. Show r => IpeArrow r -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall r. Show r => Int -> IpeArrow r -> ShowS
showsPrec :: Int -> IpeArrow r -> ShowS
$cshow :: forall r. Show r => IpeArrow r -> String
show :: IpeArrow r -> String
$cshowList :: forall r. Show r => [IpeArrow r] -> ShowS
showList :: [IpeArrow r] -> ShowS
Show,IpeArrow r -> IpeArrow r -> Bool
(IpeArrow r -> IpeArrow r -> Bool)
-> (IpeArrow r -> IpeArrow r -> Bool) -> Eq (IpeArrow r)
forall r. Eq r => IpeArrow r -> IpeArrow r -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall r. Eq r => IpeArrow r -> IpeArrow r -> Bool
== :: IpeArrow r -> IpeArrow r -> Bool
$c/= :: forall r. Eq r => IpeArrow r -> IpeArrow r -> Bool
/= :: IpeArrow r -> IpeArrow r -> Bool
Eq,(forall a b. (a -> b) -> IpeArrow a -> IpeArrow b)
-> (forall a b. a -> IpeArrow b -> IpeArrow a) -> Functor IpeArrow
forall a b. a -> IpeArrow b -> IpeArrow a
forall a b. (a -> b) -> IpeArrow a -> IpeArrow b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> IpeArrow a -> IpeArrow b
fmap :: forall a b. (a -> b) -> IpeArrow a -> IpeArrow b
$c<$ :: forall a b. a -> IpeArrow b -> IpeArrow a
<$ :: forall a b. a -> IpeArrow b -> IpeArrow a
Functor,(forall m. Monoid m => IpeArrow m -> m)
-> (forall m a. Monoid m => (a -> m) -> IpeArrow a -> m)
-> (forall m a. Monoid m => (a -> m) -> IpeArrow a -> m)
-> (forall a b. (a -> b -> b) -> b -> IpeArrow a -> b)
-> (forall a b. (a -> b -> b) -> b -> IpeArrow a -> b)
-> (forall b a. (b -> a -> b) -> b -> IpeArrow a -> b)
-> (forall b a. (b -> a -> b) -> b -> IpeArrow a -> b)
-> (forall a. (a -> a -> a) -> IpeArrow a -> a)
-> (forall a. (a -> a -> a) -> IpeArrow a -> a)
-> (forall a. IpeArrow a -> [a])
-> (forall a. IpeArrow a -> Bool)
-> (forall a. IpeArrow a -> Int)
-> (forall a. Eq a => a -> IpeArrow a -> Bool)
-> (forall a. Ord a => IpeArrow a -> a)
-> (forall a. Ord a => IpeArrow a -> a)
-> (forall a. Num a => IpeArrow a -> a)
-> (forall a. Num a => IpeArrow a -> a)
-> Foldable IpeArrow
forall a. Eq a => a -> IpeArrow a -> Bool
forall a. Num a => IpeArrow a -> a
forall a. Ord a => IpeArrow a -> a
forall m. Monoid m => IpeArrow m -> m
forall a. IpeArrow a -> Bool
forall a. IpeArrow a -> Int
forall a. IpeArrow a -> [a]
forall a. (a -> a -> a) -> IpeArrow a -> a
forall m a. Monoid m => (a -> m) -> IpeArrow a -> m
forall b a. (b -> a -> b) -> b -> IpeArrow a -> b
forall a b. (a -> b -> b) -> b -> IpeArrow a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => IpeArrow m -> m
fold :: forall m. Monoid m => IpeArrow m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> IpeArrow a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> IpeArrow a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> IpeArrow a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> IpeArrow a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> IpeArrow a -> b
foldr :: forall a b. (a -> b -> b) -> b -> IpeArrow a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> IpeArrow a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> IpeArrow a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> IpeArrow a -> b
foldl :: forall b a. (b -> a -> b) -> b -> IpeArrow a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> IpeArrow a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> IpeArrow a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> IpeArrow a -> a
foldr1 :: forall a. (a -> a -> a) -> IpeArrow a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> IpeArrow a -> a
foldl1 :: forall a. (a -> a -> a) -> IpeArrow a -> a
$ctoList :: forall a. IpeArrow a -> [a]
toList :: forall a. IpeArrow a -> [a]
$cnull :: forall a. IpeArrow a -> Bool
null :: forall a. IpeArrow a -> Bool
$clength :: forall a. IpeArrow a -> Int
length :: forall a. IpeArrow a -> Int
$celem :: forall a. Eq a => a -> IpeArrow a -> Bool
elem :: forall a. Eq a => a -> IpeArrow a -> Bool
$cmaximum :: forall a. Ord a => IpeArrow a -> a
maximum :: forall a. Ord a => IpeArrow a -> a
$cminimum :: forall a. Ord a => IpeArrow a -> a
minimum :: forall a. Ord a => IpeArrow a -> a
$csum :: forall a. Num a => IpeArrow a -> a
sum :: forall a. Num a => IpeArrow a -> a
$cproduct :: forall a. Num a => IpeArrow a -> a
product :: forall a. Num a => IpeArrow a -> a
Foldable,Functor IpeArrow
Foldable IpeArrow
(Functor IpeArrow, Foldable IpeArrow) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IpeArrow a -> f (IpeArrow b))
-> (forall (f :: * -> *) a.
Applicative f =>
IpeArrow (f a) -> f (IpeArrow a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IpeArrow a -> m (IpeArrow b))
-> (forall (m :: * -> *) a.
Monad m =>
IpeArrow (m a) -> m (IpeArrow a))
-> Traversable IpeArrow
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => IpeArrow (m a) -> m (IpeArrow a)
forall (f :: * -> *) a.
Applicative f =>
IpeArrow (f a) -> f (IpeArrow a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IpeArrow a -> m (IpeArrow b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IpeArrow a -> f (IpeArrow b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IpeArrow a -> f (IpeArrow b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IpeArrow a -> f (IpeArrow b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
IpeArrow (f a) -> f (IpeArrow a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
IpeArrow (f a) -> f (IpeArrow a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IpeArrow a -> m (IpeArrow b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IpeArrow a -> m (IpeArrow b)
$csequence :: forall (m :: * -> *) a. Monad m => IpeArrow (m a) -> m (IpeArrow a)
sequence :: forall (m :: * -> *) a. Monad m => IpeArrow (m a) -> m (IpeArrow a)
Traversable)
makeLenses ''IpeArrow
normalArrow :: IpeArrow r
normalArrow :: forall r. IpeArrow r
normalArrow = Text -> IpeSize r -> IpeArrow r
forall r. Text -> IpeSize r -> IpeArrow r
IpeArrow Text
"normal" (IpeValue r -> IpeSize r
forall r. IpeValue r -> IpeSize r
IpeSize (IpeValue r -> IpeSize r) -> IpeValue r -> IpeSize r
forall a b. (a -> b) -> a -> b
$ Text -> IpeValue r
forall v. Text -> IpeValue v
Named Text
"normal")
class IpeAttrName (a :: AttributeUniverse) where
attrName :: proxy a -> Text
instance IpeAttrName Layer where attrName :: forall (proxy :: AttributeUniverse -> *). proxy 'Layer -> Text
attrName proxy 'Layer
_ = Text
"layer"
instance IpeAttrName Matrix where attrName :: forall (proxy :: AttributeUniverse -> *). proxy 'Matrix -> Text
attrName proxy 'Matrix
_ = Text
"matrix"
instance IpeAttrName Pin where attrName :: forall (proxy :: AttributeUniverse -> *). proxy 'Pin -> Text
attrName proxy 'Pin
_ = Text
"pin"
instance IpeAttrName Transformations where attrName :: forall (proxy :: AttributeUniverse -> *).
proxy 'Transformations -> Text
attrName proxy 'Transformations
_ = Text
"transformations"
instance IpeAttrName Stroke where attrName :: forall (proxy :: AttributeUniverse -> *). proxy 'Stroke -> Text
attrName proxy 'Stroke
_ = Text
"stroke"
instance IpeAttrName Fill where attrName :: forall (proxy :: AttributeUniverse -> *). proxy 'Fill -> Text
attrName proxy 'Fill
_ = Text
"fill"
instance IpeAttrName Pen where attrName :: forall (proxy :: AttributeUniverse -> *). proxy 'Pen -> Text
attrName proxy 'Pen
_ = Text
"pen"
instance IpeAttrName Size where attrName :: forall (proxy :: AttributeUniverse -> *). proxy 'Size -> Text
attrName proxy 'Size
_ = Text
"size"
instance IpeAttrName Dash where attrName :: forall (proxy :: AttributeUniverse -> *). proxy 'Dash -> Text
attrName proxy 'Dash
_ = Text
"dash"
instance IpeAttrName LineCap where attrName :: forall (proxy :: AttributeUniverse -> *). proxy 'LineCap -> Text
attrName proxy 'LineCap
_ = Text
"cap"
instance IpeAttrName LineJoin where attrName :: forall (proxy :: AttributeUniverse -> *). proxy 'LineJoin -> Text
attrName proxy 'LineJoin
_ = Text
"join"
instance IpeAttrName FillRule where attrName :: forall (proxy :: AttributeUniverse -> *). proxy 'FillRule -> Text
attrName proxy 'FillRule
_ = Text
"fillrule"
instance IpeAttrName Arrow where attrName :: forall (proxy :: AttributeUniverse -> *). proxy 'Arrow -> Text
attrName proxy 'Arrow
_ = Text
"arrow"
instance IpeAttrName RArrow where attrName :: forall (proxy :: AttributeUniverse -> *). proxy 'RArrow -> Text
attrName proxy 'RArrow
_ = Text
"rarrow"
instance IpeAttrName StrokeOpacity where attrName :: forall (proxy :: AttributeUniverse -> *).
proxy 'StrokeOpacity -> Text
attrName proxy 'StrokeOpacity
_ = Text
"stroke-opacity"
instance IpeAttrName Opacity where attrName :: forall (proxy :: AttributeUniverse -> *). proxy 'Opacity -> Text
attrName proxy 'Opacity
_ = Text
"opacity"
instance IpeAttrName Tiling where attrName :: forall (proxy :: AttributeUniverse -> *). proxy 'Tiling -> Text
attrName proxy 'Tiling
_ = Text
"tiling"
instance IpeAttrName Gradient where attrName :: forall (proxy :: AttributeUniverse -> *). proxy 'Gradient -> Text
attrName proxy 'Gradient
_ = Text
"gradient"
instance IpeAttrName Width where attrName :: forall (proxy :: AttributeUniverse -> *). proxy 'Width -> Text
attrName proxy 'Width
_ = Text
"width"
instance IpeAttrName Height where attrName :: forall (proxy :: AttributeUniverse -> *). proxy 'Height -> Text
attrName proxy 'Height
_ = Text
"height"
instance IpeAttrName Depth where attrName :: forall (proxy :: AttributeUniverse -> *). proxy 'Depth -> Text
attrName proxy 'Depth
_ = Text
"depth"
instance IpeAttrName VAlign where attrName :: forall (proxy :: AttributeUniverse -> *). proxy 'VAlign -> Text
attrName proxy 'VAlign
_ = Text
"valign"
instance IpeAttrName HAlign where attrName :: forall (proxy :: AttributeUniverse -> *). proxy 'HAlign -> Text
attrName proxy 'HAlign
_ = Text
"halign"
instance IpeAttrName Style where attrName :: forall (proxy :: AttributeUniverse -> *). proxy 'Style -> Text
attrName proxy 'Style
_ = Text
"style"
instance IpeAttrName Clip where attrName :: forall (proxy :: AttributeUniverse -> *). proxy 'Clip -> Text
attrName proxy 'Clip
_ = Text
"clip"
writeAttrNames :: AllConstrained IpeAttrName rs => Rec f rs -> Rec (Const Text) rs
writeAttrNames :: forall (rs :: [AttributeUniverse]) (f :: AttributeUniverse -> *).
AllConstrained IpeAttrName rs =>
Rec f rs -> Rec (Const Text) rs
writeAttrNames Rec f rs
RNil = Rec (Const Text) rs
Rec (Const Text) '[]
forall {u} (a :: u -> *). Rec a '[]
RNil
writeAttrNames (f r
x :& Rec f rs
xs) = Text -> Const Text r
forall k a (b :: k). a -> Const a b
Const (f r -> Text
forall (f :: AttributeUniverse -> *) (s :: AttributeUniverse).
IpeAttrName s =>
f s -> Text
write'' f r
x) Const Text r -> Rec (Const Text) rs -> Rec (Const Text) (r : rs)
forall {u} (a :: u -> *) (r :: u) (rs :: [u]).
a r -> Rec a rs -> Rec a (r : rs)
:& Rec f rs -> Rec (Const Text) rs
forall (rs :: [AttributeUniverse]) (f :: AttributeUniverse -> *).
AllConstrained IpeAttrName rs =>
Rec f rs -> Rec (Const Text) rs
writeAttrNames Rec f rs
xs
where
write'' :: forall f s. IpeAttrName s => f s -> Text
write'' :: forall (f :: AttributeUniverse -> *) (s :: AttributeUniverse).
IpeAttrName s =>
f s -> Text
write'' f s
_ = Proxy s -> Text
forall (a :: AttributeUniverse) (proxy :: AttributeUniverse -> *).
IpeAttrName a =>
proxy a -> Text
forall (proxy :: AttributeUniverse -> *). proxy s -> Text
attrName (Proxy s
forall {k} (t :: k). Proxy t
Proxy :: Proxy s)