Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- hyper :: (HyperViewHandled id ctx, ViewId id) => id -> View id () -> View ctx ()
- module Web.Hyperbole.View.Element
- module Web.Hyperbole.View.Event
- text :: Text -> View c ()
- data Url = Url {}
- even :: Mod c -> Mod c
- data Sides a
- type Mod context = Attributes context -> Attributes context
- truncate :: Mod c
- odd :: Mod c -> Mod c
- list :: (ToClassName a, Style ListType a) => a -> Mod c
- data Position
- link :: Url -> Mod c -> View c () -> View c ()
- value :: Text -> Mod c
- data Display = Block
- offset :: Sides Length -> Mod c
- pad :: Sides Length -> Mod c
- data View context a
- style :: Text -> View c ()
- layout :: Mod c -> View c () -> View c ()
- name :: Text -> Mod c
- data None = None
- position :: Position -> Mod c
- space :: View c ()
- class ToColor a where
- colorValue :: a -> HexColor
- colorName :: a -> Text
- hover :: Mod c -> Mod c
- raw :: Text -> View c ()
- stack :: Mod c -> Layer c () -> View c ()
- popup :: Sides Length -> Mod c
- table :: Mod c -> [dt] -> Eff '[Writer [TableColumn c dt]] () -> View c ()
- data Attributes (c :: k)
- row :: Mod c -> View c () -> View c ()
- col :: Mod c -> View c () -> View c ()
- cssResetLink :: Text
- data Align
- newtype HexColor = HexColor Text
- data Media
- data Ms
- data PxRem
- data Length
- media :: Media -> Mod c -> Mod c
- data TransitionProperty
- data ListType
- data Inner = Inner
- data Shadow
- width :: Length -> Mod c
- height :: Length -> Mod c
- minWidth :: Length -> Mod c
- minHeight :: Length -> Mod c
- gap :: Length -> Mod c
- fontSize :: Length -> Mod c
- shadow :: (Style Shadow a, ToClassName a) => a -> Mod c
- rounded :: Length -> Mod c
- bg :: ToColor clr => clr -> Mod ctx
- color :: ToColor clr => clr -> Mod ctx
- bold :: Mod c
- italic :: Mod c
- underline :: Mod c
- opacity :: Float -> Mod c
- border :: Sides PxRem -> Mod c
- borderColor :: ToColor clr => clr -> Mod ctx
- pointer :: Mod c
- transition :: Ms -> TransitionProperty -> Mod c
- textAlign :: Align -> Mod c
- zIndex :: Int -> Mod c
- display :: (Style Display a, ToClassName a) => a -> Mod c
- active :: Mod c -> Mod c
- parent :: Text -> Mod c -> Mod c
- pathUrl :: [Segment] -> Url
- cleanSegment :: Segment -> Segment
- pathSegments :: Text -> [Segment]
- url :: Text -> Url
- renderUrl :: Url -> Text
- renderPath :: [Segment] -> Text
- context :: View context context
- addContext :: context -> View context () -> View c ()
- tag :: Text -> Mod c -> View c () -> View c ()
- att :: Name -> AttValue -> Mod c
- renderText :: View () () -> Text
- renderLazyText :: View () () -> Text
- renderLazyByteString :: View () () -> ByteString
- data TableColumn c dt
- data TableHead a
- el :: Mod c -> View c () -> View c ()
- el_ :: View c () -> View c ()
- none :: View c ()
- pre :: Mod c -> Text -> View c ()
- code :: Mod c -> Text -> View c ()
- script :: Text -> View c ()
- stylesheet :: Text -> View c ()
- tcol :: forall dt c. View (TableHead c) () -> (dt -> View dt ()) -> Eff '[Writer [TableColumn c dt]] ()
- th :: Mod c -> View c () -> View (TableHead c) ()
- td :: Mod () -> View () () -> View dt ()
- ol :: Mod c -> ListItem c () -> View c ()
- ul :: Mod c -> ListItem c () -> View c ()
- li :: Mod c -> View c () -> ListItem c ()
- data Layer c a
- root :: Mod c
- grow :: Mod c
- scroll :: Mod c
- nav :: Mod c -> View c () -> View c ()
- layer :: Mod c -> View c () -> Layer c ()
- hide :: Mod c
- flexRow :: Mod c
- flexCol :: Mod c
- module Web.Hyperbole.View.Embed
Documentation
module Web.Hyperbole.View.Element
module Web.Hyperbole.View.Event
Add text to a view. Not required for string literals
el_ $ do "Hello: " text user.name
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)
type Mod context = Attributes context -> Attributes context #
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"
list :: (ToClassName a, Style ListType a) => a -> Mod c #
Set the list style of an item
ol id $ do li (list Decimal) "First" li (list Decimal) "Second" li (list Decimal) "Third"
Instances
Show Position | |
ToClassName Position | |
Defined in Web.View.Style toClassName :: Position -> ClassName # | |
ToStyleValue Position | |
Defined in Web.View.Style toStyleValue :: Position -> StyleValue # |
Instances
Show Display | |
ToClassName Display | |
Defined in Web.View.Style toClassName :: Display -> ClassName # | |
ToStyleValue Display | |
Defined in Web.View.Style toStyleValue :: Display -> StyleValue # | |
Style Display Display | |
Defined in Web.View.Style styleValue :: Display -> StyleValue # | |
Style Display None | |
Defined in Web.View.Style styleValue :: None -> StyleValue # |
pad :: Sides Length -> Mod c #
Space surrounding the children of the element
To create even spacing around and between all elements:
col (pad 10 . gap 10) $ do el_ "one" el_ "two" el_ "three"
Views are HTML fragments that carry all CSS
used by any child element.
view :: View c () view = col (pad 10 . gap 10) $ do el bold "Hello" el_ "World"
They can also have a context which can be used to create type-safe or context-aware elements. See context
or table
for an example
Instances
HasViewId (View ctx :: Type -> Type) (ctx :: Type) Source # | |
Defined in Web.Hyperbole.HyperView | |
Applicative (View context) | |
Defined in Web.View.View | |
Functor (View context) | |
Monad (View context) | |
IsString (View context ()) | |
Defined in Web.View.View fromString :: String -> View context () # |
layout :: Mod c -> View c () -> View c () #
We can intuitively create layouts with combinations of row
, col
, stack
, grow
, and space
Wrap main content in layout
to allow the view to consume vertical screen space
holygrail ::View
c () holygrail =layout
id $ dorow
section "Top Bar"row
grow
$ docol
section "Left Sidebar"col
(section .grow
) "Main Content"col
section "Right Sidebar"row
section "Bottom Bar" where section =border
1
Instances
Show None | |
ToClassName None | |
Defined in Web.View.Types toClassName :: None -> ClassName # | |
ToStyleValue None | |
Defined in Web.View.Types toStyleValue :: None -> StyleValue # | |
Style Display None | |
Defined in Web.View.Style styleValue :: None -> StyleValue # | |
Style ListType None | |
Defined in Web.View.Style styleValue :: None -> StyleValue # | |
Style Shadow None | |
Defined in Web.View.Style styleValue :: None -> StyleValue # |
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"
Apply when hovering over an element
el (bg Primary . hover (bg PrimaryLight)) "Hover"
Embed static, unescaped HTML or SVG. Take care not to use raw
with user-generated content.
spinner = raw "<svg>...</svg>"
stack :: Mod c -> Layer c () -> View c () #
Stack children on top of each other. Each child has the full width. See popup
stack id $ do layer id "Background" layer (bg Black . opacity 0.5) "Overlay"
popup :: Sides Length -> Mod c #
This layer
is not included in the stack
size, and covers content outside of it. If used outside of stack, the popup is offset from the entire page.
stack id $ do layer id $ input (value "Autocomplete Box") layer (popup (TRBL 50 0 0 0)) $ do el_ "Item 1" el_ "Item 2" el_ "Item 3" el_ "This is covered by the menu"
table :: Mod c -> [dt] -> Eff '[Writer [TableColumn c dt]] () -> View c () #
Create a type safe data table by specifying columns
usersTable :: [User] -> View c () usersTable us = do table id us $ do tcol (th hd "Name") $ \u -> td cell $ text u.name tcol (th hd "Email") $ \u -> td cell $ text u.email where hd = cell . bold cell = pad 4 . border 1
data Attributes (c :: k) #
The Attributes for an Element
. Classes are merged and managed separately from the other attributes.
Instances
Monoid (Attributes c) | |
Defined in Web.View.Types mempty :: Attributes c # mappend :: Attributes c -> Attributes c -> Attributes c # mconcat :: [Attributes c] -> Attributes c # | |
Semigroup (Attributes c) | |
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) | |
Defined in Web.View.Types showsPrec :: Int -> Attributes c -> ShowS # show :: Attributes c -> String # showList :: [Attributes c] -> ShowS # | |
Eq (Attributes c) | |
Defined in Web.View.Types (==) :: Attributes c -> Attributes c -> Bool # (/=) :: Attributes c -> Attributes c -> Bool # |
row :: Mod c -> View c () -> View c () #
Lay out children in a row
row id $ do el_ "Left" space el_ "Right"
col :: Mod c -> View c () -> View c () #
Lay out children in a column.
col grow $ do el_ "Top" space el_ "Bottom"
cssResetLink :: Text #
Alternatively, the reset is available on a CDN
import Data.String.Interpolate (i) toDocument :: ByteString -> ByteString toDocument cnt = [i|<html> <head> <link rel="stylesheet" href="#{cssResetLink}"> </head> <body>#{cnt}</body> </html>|]
Instances
Show Align | |
ToClassName Align | |
Defined in Web.View.Types toClassName :: Align -> ClassName # | |
ToStyleValue Align | |
Defined in Web.View.Types toStyleValue :: Align -> StyleValue # |
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 | |
Defined in Web.View.Types fromString :: String -> HexColor # | |
Show HexColor | |
ToClassName HexColor | |
Defined in Web.View.Types toClassName :: HexColor -> ClassName # | |
ToColor HexColor | |
Defined in Web.View.Types | |
ToStyleValue HexColor | |
Defined in Web.View.Types toStyleValue :: HexColor -> StyleValue # |
Media allows for responsive designs that change based on characteristics of the window. See Layout Example
Milliseconds, used for transitions
Instances
Num Ms | |
Show Ms | |
ToClassName Ms | |
Defined in Web.View.Types toClassName :: Ms -> ClassName # | |
ToStyleValue Ms | |
Defined in Web.View.Types toStyleValue :: Ms -> StyleValue # |
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 | |
Num PxRem | |
Integral PxRem | |
Real PxRem | |
Defined in Web.View.Types toRational :: PxRem -> Rational # | |
Show PxRem | |
Eq PxRem | |
Ord PxRem | |
ToClassName PxRem | |
Defined in Web.View.Types toClassName :: PxRem -> ClassName # | |
ToStyleValue PxRem | |
Defined in Web.View.Types toStyleValue :: PxRem -> StyleValue # |
Instances
Num Length | |
Show Length | |
ToClassName Length | |
Defined in Web.View.Types toClassName :: Length -> ClassName # | |
ToStyleValue Length | |
Defined in Web.View.Types toStyleValue :: Length -> StyleValue # |
media :: Media -> Mod c -> Mod c #
Apply when the Media matches the current window. This allows for responsive designs
el (width 100 . media (MinWidth 800) (width 400)) "Big if window > 800"
data TransitionProperty #
Instances
Show TransitionProperty | |
Defined in Web.View.Style showsPrec :: Int -> TransitionProperty -> ShowS # show :: TransitionProperty -> String # showList :: [TransitionProperty] -> ShowS # |
Instances
Show ListType | |
ToClassName ListType | |
Defined in Web.View.Style toClassName :: ListType -> ClassName # | |
ToStyleValue ListType | |
Defined in Web.View.Style toStyleValue :: ListType -> StyleValue # | |
Style ListType ListType | |
Defined in Web.View.Style styleValue :: ListType -> StyleValue # | |
Style ListType None | |
Defined in Web.View.Style styleValue :: None -> StyleValue # |
Instances
Show Inner | |
ToClassName Inner | |
Defined in Web.View.Style toClassName :: Inner -> ClassName # | |
Style Shadow Inner | |
Defined in Web.View.Style styleValue :: Inner -> StyleValue # |
Instances
Style Shadow Inner | |
Defined in Web.View.Style styleValue :: Inner -> StyleValue # | |
Style Shadow None | |
Defined in Web.View.Style styleValue :: None -> StyleValue # | |
Style Shadow () | |
Defined in Web.View.Style styleValue :: () -> StyleValue # |
minHeight :: Length -> Mod c #
Allow height to grow to contents but not shrink any smaller than value
shadow :: (Style Shadow a, ToClassName a) => a -> Mod c #
Add a drop shadow to an element
input (shadow Inner) "Inset Shadow" button (shadow ()) "Click Me"
border :: Sides PxRem -> Mod c #
Set a border around the element
el (border 1) "all sides" el (border (X 1)) "only left and right"
borderColor :: ToColor clr => clr -> Mod ctx #
Set a border color. See ToColor
Use a button-like cursor when hovering over the element
Button-like elements:
btn = pointer . bg Primary . hover (bg PrimaryLight) options = row id $ do el btn "Login" el btn "Sign Up"
transition :: Ms -> TransitionProperty -> Mod c #
Animate changes to the given property
el (transition 100 (Height 400)) "Tall" el (transition 100 (Height 100)) "Small"
display :: (Style Display a, ToClassName a) => a -> Mod c #
Set container display
el (display None) HIDDEN
parent :: Text -> Mod c -> Mod c #
Apply when the element is somewhere inside an anscestor.
For example, the HTMX library applies an "htmx-request" class to the body when a request is pending. We can use this to create a loading indicator
el (pad 10) $ do el (parent "htmx-request" flexRow . hide) "Loading..." el (parent "htmx-request" hide . flexRow) "Normal Content"
cleanSegment :: Segment -> Segment #
pathSegments :: Text -> [Segment] #
renderPath :: [Segment] -> Text #
context :: View context context #
Views have a Reader
built-in for convienient access to static data, and to add type-safety to view functions. See 'Web.View.Element.ListItem and https://hackage.haskell.org/package/hyperbole/docs/Web-Hyperbole.html
numberView :: View Int () numberView = do num <- context el_ $ do "Number: " text (pack $ show num)
addContext :: context -> View context () -> View c () #
tag :: Text -> Mod c -> View c () -> View c () #
Create a new element constructor with the given tag name
aside :: Mod c -> View c () -> View c () aside = tag "aside"
att :: Name -> AttValue -> Mod c #
Set an attribute, replacing existing value
hlink :: Text -> View c () -> View c () hlink url content = tag "a" (att "href" url) content
renderText :: View () () -> Text #
Renders a View
as HTML with embedded CSS class definitions
>>>
renderText $ el bold "Hello"
<style type='text/css'>.bold { font-weight:bold }</style> <div class='bold'>Hello</div>
renderLazyText :: View () () -> Text #
renderLazyByteString :: View () () -> ByteString #
data TableColumn c dt #
stylesheet :: Text -> View c () #
tcol :: forall dt c. View (TableHead c) () -> (dt -> View dt ()) -> Eff '[Writer [TableColumn c dt]] () #
ol :: Mod c -> ListItem c () -> View c () #
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"
layer :: Mod c -> View c () -> Layer c () #
A normal layer contributes to the size of the parent. See stack
module Web.Hyperbole.View.Embed