Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- data Content
- data Element = Element {
- inline :: Bool
- name :: Name
- attributes :: Attributes ()
- children :: [Content]
- element :: Name -> Attributes c -> [Content] -> Element
- data Attributes c = Attributes {}
- type Attribute = (Name, AttValue)
- type Name = Text
- type AttValue = Text
- type Mod (context :: Type) = Attributes context -> Attributes context
- type CSS = [Class]
- data Class = Class {
- selector :: Selector
- properties :: Styles
- type Styles = Map Name StyleValue
- type Ancestor = Text
- data ChildCombinator
- data Selector = Selector {}
- selector :: ClassName -> Selector
- newtype ClassName = ClassName {}
- className :: Text -> ClassName
- class ToClassName a where
- toClassName :: a -> ClassName
- data Pseudo
- newtype StyleValue = StyleValue String
- class ToStyleValue a where
- toStyleValue :: a -> StyleValue
- data Length
- newtype PxRem = PxRem' Int
- newtype Ms = Ms Int
- data Media
- data Sides a
- newtype FlatAttributes = FlatAttributes {}
- class ToColor a where
- colorValue :: a -> HexColor
- colorName :: a -> Text
- newtype HexColor = HexColor Text
- data Align = Center
Documentation
A single HTML tag. Note that the class attribute is stored separately from the rest of the attributes to make adding styles easier
Element | |
|
data Attributes c Source #
The Attributes for an Element
. Classes are merged and managed separately from the other attributes.
Instances
Monoid (Attributes c) Source # | |
Defined in Web.View.Types mempty :: Attributes c # mappend :: Attributes c -> Attributes c -> Attributes c # mconcat :: [Attributes c] -> Attributes c # | |
Semigroup (Attributes c) Source # | |
Defined in Web.View.Types (<>) :: Attributes c -> Attributes c -> Attributes c # sconcat :: NonEmpty (Attributes c) -> Attributes c # stimes :: Integral b => b -> Attributes c -> Attributes c # | |
Show (Attributes c) Source # | |
Defined in Web.View.Types showsPrec :: Int -> Attributes c -> ShowS # show :: Attributes c -> String # showList :: [Attributes c] -> ShowS # | |
Eq (Attributes c) Source # | |
Defined in Web.View.Types (==) :: Attributes c -> Attributes c -> Bool # (/=) :: Attributes c -> Attributes c -> Bool # |
Attribute Modifiers
type Mod (context :: Type) = Attributes context -> Attributes context Source #
Element functions expect a modifier function as their first argument. These can add attributes and classes. Combine multiple Mod
s with (.
)
userEmail :: User -> View c () userEmail user = input (fontSize 16 . active) (text user.email) where active = isActive user then bold else id
If you don't want to specify any attributes, you can use id
plainView :: View c () plainView = el id "No styles"
Atomic CSS
Atomic classes include a selector and the corresponding styles
Class | |
|
A parent selector limits the selector to only apply when a descendent of the parent in question
data ChildCombinator Source #
A child selector limits
Instances
IsString ChildCombinator Source # | |
Defined in Web.View.Types fromString :: String -> ChildCombinator # | |
Show ChildCombinator Source # | |
Defined in Web.View.Types showsPrec :: Int -> ChildCombinator -> ShowS # show :: ChildCombinator -> String # showList :: [ChildCombinator] -> ShowS # | |
Eq ChildCombinator Source # | |
Defined in Web.View.Types (==) :: ChildCombinator -> ChildCombinator -> Bool # (/=) :: ChildCombinator -> ChildCombinator -> Bool # | |
Ord ChildCombinator Source # | |
Defined in Web.View.Types compare :: ChildCombinator -> ChildCombinator -> Ordering # (<) :: ChildCombinator -> ChildCombinator -> Bool # (<=) :: ChildCombinator -> ChildCombinator -> Bool # (>) :: ChildCombinator -> ChildCombinator -> Bool # (>=) :: ChildCombinator -> ChildCombinator -> Bool # max :: ChildCombinator -> ChildCombinator -> ChildCombinator # min :: ChildCombinator -> ChildCombinator -> ChildCombinator # |
The selector to use for the given atomic Class
A class name
class ToClassName a where Source #
Convert a type into a className segment to generate unique compound style names based on the value
Nothing
toClassName :: a -> ClassName Source #
default toClassName :: Show a => a -> ClassName Source #
Instances
ToClassName Text Source # | |
Defined in Web.View.Types toClassName :: Text -> ClassName Source # | |
ToClassName Align Source # | |
Defined in Web.View.Types toClassName :: Align -> ClassName Source # | |
ToClassName HexColor Source # | |
Defined in Web.View.Types toClassName :: HexColor -> ClassName Source # | |
ToClassName Length Source # | |
Defined in Web.View.Types toClassName :: Length -> ClassName Source # | |
ToClassName Ms Source # | |
Defined in Web.View.Types toClassName :: Ms -> ClassName Source # | |
ToClassName PxRem Source # | |
Defined in Web.View.Types toClassName :: PxRem -> ClassName Source # | |
ToClassName Float Source # | |
Defined in Web.View.Types toClassName :: Float -> ClassName Source # | |
ToClassName Int Source # | |
Defined in Web.View.Types toClassName :: Int -> ClassName Source # |
Psuedos allow for specifying styles that only apply in certain conditions. See hover
etc
el (color Primary . hover (color White)) "hello"
newtype StyleValue Source #
The value of a css style property
Instances
IsString StyleValue Source # | |
Defined in Web.View.Types fromString :: String -> StyleValue # | |
Show StyleValue Source # | |
Defined in Web.View.Types showsPrec :: Int -> StyleValue -> ShowS # show :: StyleValue -> String # showList :: [StyleValue] -> ShowS # | |
Eq StyleValue Source # | |
Defined in Web.View.Types (==) :: StyleValue -> StyleValue -> Bool # (/=) :: StyleValue -> StyleValue -> Bool # |
class ToStyleValue a where Source #
Use a type as a css style property value
Nothing
toStyleValue :: a -> StyleValue Source #
default toStyleValue :: Show a => a -> StyleValue Source #
Instances
ToStyleValue Text Source # | |
Defined in Web.View.Types toStyleValue :: Text -> StyleValue Source # | |
ToStyleValue Align Source # | |
Defined in Web.View.Types toStyleValue :: Align -> StyleValue Source # | |
ToStyleValue HexColor Source # | |
Defined in Web.View.Types toStyleValue :: HexColor -> StyleValue Source # | |
ToStyleValue Length Source # | |
Defined in Web.View.Types toStyleValue :: Length -> StyleValue Source # | |
ToStyleValue Ms Source # | |
Defined in Web.View.Types toStyleValue :: Ms -> StyleValue Source # | |
ToStyleValue PxRem Source # | |
Defined in Web.View.Types toStyleValue :: PxRem -> StyleValue Source # | |
ToStyleValue String Source # | |
Defined in Web.View.Types toStyleValue :: String -> StyleValue Source # | |
ToStyleValue Float Source # | |
Defined in Web.View.Types toStyleValue :: Float -> StyleValue Source # | |
ToStyleValue Int Source # | |
Defined in Web.View.Types toStyleValue :: Int -> StyleValue Source # |
Instances
Num Length Source # | |
Show Length Source # | |
ToClassName Length Source # | |
Defined in Web.View.Types toClassName :: Length -> ClassName Source # | |
ToStyleValue Length Source # | |
Defined in Web.View.Types toStyleValue :: Length -> StyleValue Source # |
Px, converted to Rem. Allows for the user to change the document font size and have the app scale accordingly. But allows the programmer to code in pixels to match a design
Instances
Enum PxRem Source # | |
Num PxRem Source # | |
Integral PxRem Source # | |
Real PxRem Source # | |
Defined in Web.View.Types toRational :: PxRem -> Rational # | |
Show PxRem Source # | |
Eq PxRem Source # | |
Ord PxRem Source # | |
ToClassName PxRem Source # | |
Defined in Web.View.Types toClassName :: PxRem -> ClassName Source # | |
ToStyleValue PxRem Source # | |
Defined in Web.View.Types toStyleValue :: PxRem -> StyleValue Source # |
Milliseconds, used for transitions
Instances
Num Ms Source # | |
Show Ms Source # | |
ToClassName Ms Source # | |
Defined in Web.View.Types toClassName :: Ms -> ClassName Source # | |
ToStyleValue Ms Source # | |
Defined in Web.View.Types toStyleValue :: Ms -> StyleValue Source # |
Media allows for responsive designs that change based on characteristics of the window. See Layout Example
Options for styles that support specifying various sides. This has a "fake" Num instance to support literals
border 5 border (X 2) border (TRBL 0 5 0 0)
Instances
newtype FlatAttributes Source #
Element's attributes do not include class, which is separated. FlatAttributes generate the class attribute and include it
Instances
Generic FlatAttributes Source # | |
Defined in Web.View.Types type Rep FlatAttributes :: Type -> Type # from :: FlatAttributes -> Rep FlatAttributes x # to :: Rep FlatAttributes x -> FlatAttributes # | |
type Rep FlatAttributes Source # | |
Defined in Web.View.Types type Rep FlatAttributes = D1 ('MetaData "FlatAttributes" "Web.View.Types" "web-view-0.6.0-FiVFgZlXrqrCibFqggEU8Z" 'True) (C1 ('MetaCons "FlatAttributes" 'PrefixI 'True) (S1 ('MetaSel ('Just "attributes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Name AttValue)))) |
Colors
class ToColor a where Source #
ToColor allows you to create a type containing your application's colors:
data AppColor = White | Primary | Dark instance ToColor AppColor where colorValue White = "#FFF" colorValue Dark = "#333" colorValue Primary = "#00F" hello :: View c () hello = el (bg Primary . color White) "Hello"
colorValue :: a -> HexColor Source #
Hexidecimal Color. Can be specified with or without the leading #
. Recommended to use an AppColor type instead of manually using hex colors. See ToColor
Instances
IsString HexColor Source # | |
Defined in Web.View.Types fromString :: String -> HexColor # | |
Show HexColor Source # | |
ToClassName HexColor Source # | |
Defined in Web.View.Types toClassName :: HexColor -> ClassName Source # | |
ToColor HexColor Source # | |
ToStyleValue HexColor Source # | |
Defined in Web.View.Types toStyleValue :: HexColor -> StyleValue Source # |
Instances
Show Align Source # | |
ToClassName Align Source # | |
Defined in Web.View.Types toClassName :: Align -> ClassName Source # | |
ToStyleValue Align Source # | |
Defined in Web.View.Types toStyleValue :: Align -> StyleValue Source # |