Copyright | (c) 2017 Cristian Adrián Ontivero |
---|---|
License | BSD3 |
Stability | experimental |
Portability | unknown |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data BasicShape
- data ShapeRadius
- data AtMost2 a
- data FillRule
Documentation
data BasicShape Source #
CSS <basic-shape> data type.
Inset (NonEmpty ShapeArg) (Maybe BorderRadius) | |
Circle (Maybe ShapeRadius) (Maybe Position) | |
Ellipse (AtMost2 ShapeRadius) (Maybe Position) | |
Polygon (Maybe FillRule) (NonEmpty (ShapeArg, ShapeArg)) |
Instances
Eq BasicShape Source # | |
Defined in Hasmin.Types.BasicShape (==) :: BasicShape -> BasicShape -> Bool # (/=) :: BasicShape -> BasicShape -> Bool # | |
Show BasicShape Source # | |
Defined in Hasmin.Types.BasicShape showsPrec :: Int -> BasicShape -> ShowS # show :: BasicShape -> String # showList :: [BasicShape] -> ShowS # | |
ToText BasicShape Source # | |
Defined in Hasmin.Types.BasicShape toText :: BasicShape -> Text Source # toBuilder :: BasicShape -> Builder Source # | |
Minifiable BasicShape Source # | |
Defined in Hasmin.Types.BasicShape minify :: BasicShape -> Reader Config BasicShape Source # |
data ShapeRadius Source #
Instances
Eq ShapeRadius Source # | |
Defined in Hasmin.Types.BasicShape (==) :: ShapeRadius -> ShapeRadius -> Bool # (/=) :: ShapeRadius -> ShapeRadius -> Bool # | |
Show ShapeRadius Source # | |
Defined in Hasmin.Types.BasicShape showsPrec :: Int -> ShapeRadius -> ShowS # show :: ShapeRadius -> String # showList :: [ShapeRadius] -> ShowS # | |
ToText ShapeRadius Source # | |
Defined in Hasmin.Types.BasicShape toText :: ShapeRadius -> Text Source # toBuilder :: ShapeRadius -> Builder Source # |
Instances
Functor AtMost2 Source # | |
Foldable AtMost2 Source # | |
Defined in Hasmin.Types.BasicShape fold :: Monoid m => AtMost2 m -> m # foldMap :: Monoid m => (a -> m) -> AtMost2 a -> m # foldr :: (a -> b -> b) -> b -> AtMost2 a -> b # foldr' :: (a -> b -> b) -> b -> AtMost2 a -> b # foldl :: (b -> a -> b) -> b -> AtMost2 a -> b # foldl' :: (b -> a -> b) -> b -> AtMost2 a -> b # foldr1 :: (a -> a -> a) -> AtMost2 a -> a # foldl1 :: (a -> a -> a) -> AtMost2 a -> a # elem :: Eq a => a -> AtMost2 a -> Bool # maximum :: Ord a => AtMost2 a -> a # minimum :: Ord a => AtMost2 a -> a # | |
Traversable AtMost2 Source # | |
Eq a => Eq (AtMost2 a) Source # | |
Show a => Show (AtMost2 a) Source # | |