| Safe Haskell | Safe-Inferred |
|---|---|
| Language | GHC2021 |
Web.Hyperbole.View
Synopsis
- newtype View c a = View {}
- text :: Text -> View c ()
- none :: View c ()
- tag :: Text -> View c () -> View c ()
- raw :: Text -> View c ()
- addContext :: ctx -> View ctx () -> View c ()
- context :: forall c. View c c
- modifyContext :: forall ctx0 ctx1. (ctx0 -> ctx1) -> View ctx1 () -> View ctx0 ()
- module Web.Hyperbole.View.Embed
- module Web.Hyperbole.View.Render
- newtype Table c a = Table (View c a)
- newtype TableColumns c dt a = TableColumns (Eff '[State [TableColumn c dt]] a)
- newtype TableHead id a = TableHead (View id a)
- data TableColumn c dt = TableColumn {}
- newtype ListItem c a = ListItem (View c a)
- pre :: Text -> View c ()
- link :: URI -> View c () -> View c ()
- value :: Attributable h => Text -> Attributes h -> Attributes h
- style :: ByteString -> View c ()
- name :: Attributable h => Text -> Attributes h -> Attributes h
- space :: View c ()
- col :: View c () -> View c ()
- row :: View c () -> View c ()
- el :: View c () -> View c ()
- placeholder :: Attributable h => Text -> Attributes h -> Attributes h
- script' :: ByteString -> View c ()
- type_ :: Attributable h => Text -> Attributes h -> Attributes h
- code :: Text -> View c ()
- src :: Attributable h => Text -> Attributes h -> Attributes h
- td :: View c () -> View c ()
- table :: [dt] -> TableColumns c dt () -> View c ()
- content :: Attributable h => Text -> Attributes h -> Attributes h
- img :: Text -> View c ()
- autofocus :: Attributable h => Attributes h -> Attributes h
- meta :: View c ()
- title :: Text -> View c ()
- httpEquiv :: Attributable h => Text -> Attributes h -> Attributes h
- charset :: Attributable h => Text -> Attributes h -> Attributes h
- script :: Text -> View c ()
- stylesheet :: Text -> View c ()
- nav :: View c () -> View c ()
- usersTable :: View c ()
- tcol :: forall dt c. TableHead c () -> (dt -> View c ()) -> TableColumns c dt ()
- th :: View c () -> TableHead c ()
- ol :: ListItem c () -> View c ()
- ul :: ListItem c () -> View c ()
- li :: View c () -> ListItem c ()
- module Web.Hyperbole.View.CSS
- module Web.Atomic.Attributes
Documentation
Instances
| HasViewId (View ctx :: Type -> Type) (ctx :: Type) Source # | |
Defined in Web.Hyperbole.HyperView.ViewId | |
| Applicative (View ctx) Source # | |
| Functor (View c) Source # | |
| Monad (View ctx) Source # | |
| IsString (View c ()) Source # | |
Defined in Web.Hyperbole.View.Types Methods fromString :: String -> View c () # | |
| Attributable (View c a) Source # | |
Defined in Web.Hyperbole.View.Types | |
| Styleable (View c a) Source # | |
| Styleable (TableColumns c dt () -> View c ()) Source # | |
Defined in Web.Hyperbole.View.Tag Methods (~) :: (TableColumns c dt () -> View c ()) -> (CSS (TableColumns c dt () -> View c ()) -> CSS (TableColumns c dt () -> View c ())) -> TableColumns c dt () -> View c () # modCSS :: ([Rule] -> [Rule]) -> (TableColumns c dt () -> View c ()) -> TableColumns c dt () -> View c () # | |
addContext :: ctx -> View ctx () -> View c () Source #
modifyContext :: forall ctx0 ctx1. (ctx0 -> ctx1) -> View ctx1 () -> View ctx0 () Source #
module Web.Hyperbole.View.Embed
module Web.Hyperbole.View.Render
newtype TableColumns c dt a Source #
Constructors
| TableColumns (Eff '[State [TableColumn c dt]] a) |
Instances
newtype TableHead id a Source #
Instances
| Applicative (TableHead id) Source # | |
Defined in Web.Hyperbole.View.Tag | |
| Functor (TableHead id) Source # | |
| Monad (TableHead id) Source # | |
| Styleable (TableHead id a) Source # | |
data TableColumn c dt Source #
Constructors
| TableColumn | |
value :: Attributable h => Text -> Attributes h -> Attributes h Source #
style :: ByteString -> View c () Source #
name :: Attributable h => Text -> Attributes h -> Attributes h Source #
placeholder :: Attributable h => Text -> Attributes h -> Attributes h Source #
type_ :: Attributable h => Text -> Attributes h -> Attributes h Source #
src :: Attributable h => Text -> Attributes h -> Attributes h Source #
table :: [dt] -> TableColumns c dt () -> View c () Source #
Create a type safe data table by specifying columns
data User = User {name :: Text, email :: Text}
usersTable :: [User] -> View c ()
usersTable us = do
table us $ do
tcol (th "Name" ~ hd) $ \u -> td ~ cell $ text u.name
tcol (th "Email" ~ hd) $ \u -> td ~ cell $ text u.email
where
hd = cell . bold
cell :: (Styleable h) => CSS h -> CSS h
cell = pad 4 . border 1content :: Attributable h => Text -> Attributes h -> Attributes h Source #
autofocus :: Attributable h => Attributes h -> Attributes h Source #
httpEquiv :: Attributable h => Text -> Attributes h -> Attributes h Source #
charset :: Attributable h => Text -> Attributes h -> Attributes h Source #
stylesheet :: Text -> View c () Source #
usersTable :: View c () Source #
ol :: ListItem c () -> View c () Source #
List elements do not include any inherent styling but are useful for accessibility. See list.
ol id $ do let nums = list Decimal li nums "one" li nums "two" li nums "three"
module Web.Hyperbole.View.CSS
module Web.Atomic.Attributes