hyperbole-0.4.2: Interactive HTML apps using type-safe serverside Haskell
Safe HaskellNone
LanguageGHC2021

Web.Hyperbole.View

Synopsis

Documentation

hyper :: (HyperViewHandled id ctx, ViewId id) => id -> View id () -> View ctx () Source #

Embed a HyperView into another View

page :: Eff es (Page '[Message])
page = do
  pure $ do
    col (pad 10 . gap 10) $ do
      el (bold . fontSize 24) "Unchanging Header"
      hyper Message $ messageView "Hello World"

text :: Text -> View c () #

Add text to a view. Not required for string literals

el_ $ do
  "Hello: "
  text user.name

data Url #

Constructors

Url 

Fields

Instances

Instances details
IsString Url 
Instance details

Defined in Web.View.Types.Url

Methods

fromString :: String -> Url #

Monoid Url 
Instance details

Defined in Web.View.Types.Url

Methods

mempty :: Url #

mappend :: Url -> Url -> Url #

mconcat :: [Url] -> Url #

Semigroup Url 
Instance details

Defined in Web.View.Types.Url

Methods

(<>) :: Url -> Url -> Url #

sconcat :: NonEmpty Url -> Url #

stimes :: Integral b => b -> Url -> Url #

Read Url 
Instance details

Defined in Web.View.Types.Url

Show Url 
Instance details

Defined in Web.View.Types.Url

Methods

showsPrec :: Int -> Url -> ShowS #

show :: Url -> String #

showList :: [Url] -> ShowS #

Eq Url 
Instance details

Defined in Web.View.Types.Url

Methods

(==) :: Url -> Url -> Bool #

(/=) :: Url -> Url -> Bool #

even :: Mod c -> Mod c #

Apply to even-numbered children

data Sides a #

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)

Constructors

All a 
TRBL a a a a 
X a 
Y a 
XY a a 
T a 
R a 
B a 
L a 
TR a a 
TL a a 
BR a a 
BL a a 

Instances

Instances details
Num a => Num (Sides a) 
Instance details

Defined in Web.View.Types

Methods

(+) :: Sides a -> Sides a -> Sides a #

(-) :: Sides a -> Sides a -> Sides a #

(*) :: Sides a -> Sides a -> Sides a #

negate :: Sides a -> Sides a #

abs :: Sides a -> Sides a #

signum :: Sides a -> Sides a #

fromInteger :: Integer -> Sides a #

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 Mods 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"

truncate :: Mod c #

Cut off the contents of the element

odd :: Mod c -> Mod c #

Apply to odd-numbered children

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"

data Position #

Constructors

Absolute 
Fixed 
Sticky 
Relative 

Instances

Instances details
Show Position 
Instance details

Defined in Web.View.Style

ToClassName Position 
Instance details

Defined in Web.View.Style

ToStyleValue Position 
Instance details

Defined in Web.View.Style

link :: Url -> Mod c -> View c () -> View c () #

A hyperlink to the given url

value :: Text -> Mod c #

data Display #

Constructors

Block 

Instances

Instances details
Show Display 
Instance details

Defined in Web.View.Style

ToClassName Display 
Instance details

Defined in Web.View.Style

ToStyleValue Display 
Instance details

Defined in Web.View.Style

Style Display Display 
Instance details

Defined in Web.View.Style

Style Display None 
Instance details

Defined in Web.View.Style

offset :: Sides Length -> Mod c #

Set top, bottom, right, and left. See stack and popup

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"

data View context a #

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

Instances details
HasViewId (View ctx :: Type -> Type) (ctx :: Type) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

viewId :: View ctx ctx Source #

Applicative (View context) 
Instance details

Defined in Web.View.View

Methods

pure :: a -> View context a #

(<*>) :: View context (a -> b) -> View context a -> View context b #

liftA2 :: (a -> b -> c) -> View context a -> View context b -> View context c #

(*>) :: View context a -> View context b -> View context b #

(<*) :: View context a -> View context b -> View context a #

Functor (View context) 
Instance details

Defined in Web.View.View

Methods

fmap :: (a -> b) -> View context a -> View context b #

(<$) :: a -> View context b -> View context a #

Monad (View context) 
Instance details

Defined in Web.View.View

Methods

(>>=) :: View context a -> (a -> View context b) -> View context b #

(>>) :: View context a -> View context b -> View context b #

return :: a -> View context a #

IsString (View context ()) 
Instance details

Defined in Web.View.View

Methods

fromString :: String -> View context () #

style :: Text -> View c () #

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 $ do
  row section "Top Bar"
  row grow $ do
    col section "Left Sidebar"
    col (section . grow) "Main Content"
    col section "Right Sidebar"
  row section "Bottom Bar"
  where section = border 1

name :: Text -> Mod c #

data None #

Constructors

None 

Instances

Instances details
Show None 
Instance details

Defined in Web.View.Types

Methods

showsPrec :: Int -> None -> ShowS #

show :: None -> String #

showList :: [None] -> ShowS #

ToClassName None 
Instance details

Defined in Web.View.Types

ToStyleValue None 
Instance details

Defined in Web.View.Types

Style Display None 
Instance details

Defined in Web.View.Style

Style ListType None 
Instance details

Defined in Web.View.Style

Style Shadow None 
Instance details

Defined in Web.View.Style

position :: Position -> Mod c #

position:absolute, relative, etc. See stack and popup

space :: View c () #

Space that fills the available space in the parent row or col.

row id $ do
 space
 el_ "Right"

This is equivalent to an empty element with grow

space = el grow none

class ToColor a where #

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"

Minimal complete definition

colorValue

Methods

colorValue :: a -> HexColor #

colorName :: a -> Text #

default colorName :: Show a => a -> Text #

Instances

Instances details
ToColor HexColor 
Instance details

Defined in Web.View.Types

hover :: Mod c -> Mod c #

Apply when hovering over an element

el (bg Primary . hover (bg PrimaryLight)) "Hover"

raw :: Text -> View c () #

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

Instances details
Monoid (Attributes c) 
Instance details

Defined in Web.View.Types

Semigroup (Attributes c) 
Instance details

Defined in Web.View.Types

Show (Attributes c) 
Instance details

Defined in Web.View.Types

Eq (Attributes c) 
Instance details

Defined in Web.View.Types

Methods

(==) :: 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>|]

data Align #

Instances

Instances details
Show Align 
Instance details

Defined in Web.View.Types

Methods

showsPrec :: Int -> Align -> ShowS #

show :: Align -> String #

showList :: [Align] -> ShowS #

ToClassName Align 
Instance details

Defined in Web.View.Types

ToStyleValue Align 
Instance details

Defined in Web.View.Types

newtype HexColor #

Hexidecimal Color. Can be specified with or without the leading #. Recommended to use an AppColor type instead of manually using hex colors. See ToColor

Constructors

HexColor Text 

Instances

Instances details
IsString HexColor 
Instance details

Defined in Web.View.Types

Show HexColor 
Instance details

Defined in Web.View.Types

ToClassName HexColor 
Instance details

Defined in Web.View.Types

ToColor HexColor 
Instance details

Defined in Web.View.Types

ToStyleValue HexColor 
Instance details

Defined in Web.View.Types

data Media #

Media allows for responsive designs that change based on characteristics of the window. See Layout Example

Constructors

MinWidth Int 
MaxWidth Int 

Instances

Instances details
Show Media 
Instance details

Defined in Web.View.Types

Methods

showsPrec :: Int -> Media -> ShowS #

show :: Media -> String #

showList :: [Media] -> ShowS #

Eq Media 
Instance details

Defined in Web.View.Types

Methods

(==) :: Media -> Media -> Bool #

(/=) :: Media -> Media -> Bool #

Ord Media 
Instance details

Defined in Web.View.Types

Methods

compare :: Media -> Media -> Ordering #

(<) :: Media -> Media -> Bool #

(<=) :: Media -> Media -> Bool #

(>) :: Media -> Media -> Bool #

(>=) :: Media -> Media -> Bool #

max :: Media -> Media -> Media #

min :: Media -> Media -> Media #

data Ms #

Milliseconds, used for transitions

Instances

Instances details
Num Ms 
Instance details

Defined in Web.View.Types

Methods

(+) :: Ms -> Ms -> Ms #

(-) :: Ms -> Ms -> Ms #

(*) :: Ms -> Ms -> Ms #

negate :: Ms -> Ms #

abs :: Ms -> Ms #

signum :: Ms -> Ms #

fromInteger :: Integer -> Ms #

Show Ms 
Instance details

Defined in Web.View.Types

Methods

showsPrec :: Int -> Ms -> ShowS #

show :: Ms -> String #

showList :: [Ms] -> ShowS #

ToClassName Ms 
Instance details

Defined in Web.View.Types

Methods

toClassName :: Ms -> ClassName #

ToStyleValue Ms 
Instance details

Defined in Web.View.Types

data PxRem #

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

Instances details
Enum PxRem 
Instance details

Defined in Web.View.Types

Num PxRem 
Instance details

Defined in Web.View.Types

Integral PxRem 
Instance details

Defined in Web.View.Types

Real PxRem 
Instance details

Defined in Web.View.Types

Methods

toRational :: PxRem -> Rational #

Show PxRem 
Instance details

Defined in Web.View.Types

Methods

showsPrec :: Int -> PxRem -> ShowS #

show :: PxRem -> String #

showList :: [PxRem] -> ShowS #

Eq PxRem 
Instance details

Defined in Web.View.Types

Methods

(==) :: PxRem -> PxRem -> Bool #

(/=) :: PxRem -> PxRem -> Bool #

Ord PxRem 
Instance details

Defined in Web.View.Types

Methods

compare :: PxRem -> PxRem -> Ordering #

(<) :: PxRem -> PxRem -> Bool #

(<=) :: PxRem -> PxRem -> Bool #

(>) :: PxRem -> PxRem -> Bool #

(>=) :: PxRem -> PxRem -> Bool #

max :: PxRem -> PxRem -> PxRem #

min :: PxRem -> PxRem -> PxRem #

ToClassName PxRem 
Instance details

Defined in Web.View.Types

ToStyleValue PxRem 
Instance details

Defined in Web.View.Types

data Length #

Constructors

PxRem PxRem 
Pct Float 

Instances

Instances details
Num Length 
Instance details

Defined in Web.View.Types

Show Length 
Instance details

Defined in Web.View.Types

ToClassName Length 
Instance details

Defined in Web.View.Types

ToStyleValue Length 
Instance details

Defined in Web.View.Types

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 ListType #

Constructors

Decimal 
Disc 

Instances

Instances details
Show ListType 
Instance details

Defined in Web.View.Style

ToClassName ListType 
Instance details

Defined in Web.View.Style

ToStyleValue ListType 
Instance details

Defined in Web.View.Style

Style ListType ListType 
Instance details

Defined in Web.View.Style

Style ListType None 
Instance details

Defined in Web.View.Style

data Inner #

Constructors

Inner 

Instances

Instances details
Show Inner 
Instance details

Defined in Web.View.Style

Methods

showsPrec :: Int -> Inner -> ShowS #

show :: Inner -> String #

showList :: [Inner] -> ShowS #

ToClassName Inner 
Instance details

Defined in Web.View.Style

Style Shadow Inner 
Instance details

Defined in Web.View.Style

data Shadow #

Instances

Instances details
Style Shadow Inner 
Instance details

Defined in Web.View.Style

Style Shadow None 
Instance details

Defined in Web.View.Style

Style Shadow () 
Instance details

Defined in Web.View.Style

Methods

styleValue :: () -> StyleValue #

width :: Length -> Mod c #

Set to a specific width

height :: Length -> Mod c #

Set to a specific height

minWidth :: Length -> Mod c #

Allow width to grow to contents but not shrink any smaller than value

minHeight :: Length -> Mod c #

Allow height to grow to contents but not shrink any smaller than value

gap :: Length -> Mod c #

The space between child elements. See pad

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"

rounded :: Length -> Mod c #

Round the corners of the element

bg :: ToColor clr => clr -> Mod ctx #

Set the background color. See ToColor

color :: ToColor clr => clr -> Mod ctx #

Set the text color. See ToColor

bold :: Mod c #

italic :: Mod c #

opacity :: Float -> Mod c #

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

pointer :: Mod c #

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"

zIndex :: Int -> Mod c #

display :: (Style Display a, ToClassName a) => a -> Mod c #

Set container display

el (display None) HIDDEN

active :: Mod c -> Mod c #

Apply when the mouse is pressed down on an element

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"

url :: Text -> Url #

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 () #

Run a view with a specific context in a parent View with a different context.

parentView :: View c ()
parentView = do
  addContext 1 numberView
  addContext 2 numberView
  addContext 3 numberView

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>

data TableColumn c dt #

data TableHead a #

el :: Mod c -> View c () -> View c () #

A basic element

el (bold . pad 10) "Hello"

el_ :: View c () -> View c () #

A basic element, with no modifiers

el_ "Hello"

none :: View c () #

Do not show any content

if isVisible
 then content
 else none

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 () #

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"

ul :: Mod c -> ListItem c () -> View c () #

li :: Mod c -> View c () -> ListItem c () #

data Layer c a #

Instances

Instances details
Applicative (Layer c) 
Instance details

Defined in Web.View.Layout

Methods

pure :: a -> Layer c a #

(<*>) :: Layer c (a -> b) -> Layer c a -> Layer c b #

liftA2 :: (a -> b -> c0) -> Layer c a -> Layer c b -> Layer c c0 #

(*>) :: Layer c a -> Layer c b -> Layer c b #

(<*) :: Layer c a -> Layer c b -> Layer c a #

Functor (Layer c) 
Instance details

Defined in Web.View.Layout

Methods

fmap :: (a -> b) -> Layer c a -> Layer c b #

(<$) :: a -> Layer c b -> Layer c a #

Monad (Layer c) 
Instance details

Defined in Web.View.Layout

Methods

(>>=) :: Layer c a -> (a -> Layer c b) -> Layer c b #

(>>) :: Layer c a -> Layer c b -> Layer c b #

return :: a -> Layer c a #

root :: Mod c #

As layout but as a Mod

holygrail = col root $ do
  ...

grow :: Mod c #

Grow to fill the available space in the parent row or col

row id $ do
 el grow none
 el_ "Right"

scroll :: Mod c #

Make a fixed layout by putting scroll on a child-element

document = row root $ do
  nav (width 300) "Sidebar"
  col (grow . scroll) "Main Content"

nav :: Mod c -> View c () -> View c () #

A Nav element

layer :: Mod c -> View c () -> Layer c () #

A normal layer contributes to the size of the parent. See stack

hide :: Mod c #

Hide an element. See display

flexRow :: Mod c #

Set container to be a row. Favor row when possible

flexCol :: Mod c #

Set container to be a column. Favor col when possible