hyperbole-0.2.0: Web Framework inspired by HTMX
Safe HaskellSafe-Inferred
LanguageGHC2021

Web.Hyperbole

Synopsis

Documentation

type Mod = Attributes -> Attributes #

Element functions expect a Mod function as their first argument that adds attributes and classes.

userEmail :: User -> View c ()
userEmail user = input (fontSize 16 . active) (text user.email)
  where
    active = isActive user then bold else id

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 table for an example

Instances

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

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

ToColor HexColor 
Instance details

Defined in Web.View.Types

ToStyleValue HexColor 
Instance details

Defined in Web.View.Types

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 #

Instances

Instances details
ToColor HexColor 
Instance details

Defined in Web.View.Types

newtype Url #

Constructors

Url Text 

Instances

Instances details
IsString Url 
Instance details

Defined in Web.View.Types

Methods

fromString :: String -> Url #

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 

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 #

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

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
Num PxRem 
Instance details

Defined in Web.View.Types

Show PxRem 
Instance details

Defined in Web.View.Types

Methods

showsPrec :: Int -> PxRem -> ShowS #

show :: PxRem -> String #

showList :: [PxRem] -> ShowS #

ToClassName PxRem 
Instance details

Defined in Web.View.Types

Methods

toClassName :: PxRem -> Text #

ToStyleValue PxRem 
Instance details

Defined in Web.View.Types

data TransitionProperty #

Constructors

Width PxRem 
Height PxRem 

Instances

Instances details
Show TransitionProperty 
Instance details

Defined in Web.View.Style

text :: Text -> View c () #

Add text to a view. Not required for string literals

el_ $ do
  "Hello: "
  text user.name

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

even :: Mod -> Mod #

Apply to even-numbered children

odd :: Mod -> Mod #

Apply to odd-numbered children

value :: Text -> Mod #

pad :: Sides PxRem -> Mod #

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"

style :: Text -> View c () #

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

We can intuitively create layouts with combindations of row, col, 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 #

hover :: Mod -> Mod #

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

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

Lay out children in a row

row id $ do
   el_ "Left"
   space
   el_ "Right"

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

Lay out children in a column.

col grow $ do
   el_ "Top"
   space
   el_ "Bottom"

table :: Mod -> [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

cssResetEmbed :: ByteString #

Default CSS to remove unintuitive default styles. This or cssResetLink is required.

import Data.String.Interpolate (i)

toDocument :: Text -> Text
toDocument cnt =
  [i|<html>
    <head>
      <style type="text/css">#{cssResetEmbed}</style>
    </head>
    <body>#{cnt}</body>
  </html>|]

cssResetLink :: Text #

Alternatively, the reset is available as on a CDN

import Data.String.Interpolate (i)

toDocument :: Text -> Text
toDocument cnt =
  [i|<html>
    <head>
      <link rel="stylesheet" href="#{cssResetEmbed}">
    </head>
    <body>#{cnt}</body>
  </html>|]

width :: PxRem -> Mod #

Set to a specific width

height :: PxRem -> Mod #

Set to a specific height

minWidth :: PxRem -> Mod #

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

minHeight :: PxRem -> Mod #

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

gap :: PxRem -> Mod #

The space between child elements. See pad

flexRow :: Mod #

Set container to be a row. Favor row when possible

flexCol :: Mod #

Set container to be a column. Favor col when possible

shadow :: Mod #

Adds a basic drop shadow to an element

rounded :: PxRem -> Mod #

Round the corners of the element

bg :: ToColor c => c -> Mod #

Set the background color. See ToColor

color :: ToColor c => c -> Mod #

Set the text color. See ToColor

hide :: Mod #

Hide an element. See parent and media

border :: Sides PxRem -> Mod #

Set a border around the element

el (border 1) "all sides"
el (border (X 1)) "only left and right"

borderColor :: ToColor c => c -> Mod #

Set a border color. See ToColor

pointer :: Mod #

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 #

Animate changes to the given property

el (transition 100 (Height 400)) "Tall"
el (transition 100 (Height 100)) "Small"

active :: Mod -> Mod #

Apply when the mouse is pressed down on an element

media :: Media -> Mod -> Mod #

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"

parent :: Text -> Mod -> Mod #

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"

context :: View context context #

Get the current context

addContext :: context -> View context () -> View c () #

Run a view with a specific context in a parent View with a different context. This can be used to create type safe view functions, like table

tag :: Text -> Mod -> View c () -> View c () #

Create a new element constructor

aside :: Mod -> View c () -> View c ()
aside = tag "aside"

att :: Name -> AttValue -> Mod #

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>

el :: Mod -> 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 -> 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 -> View c () -> View (TableHead c) () #

td :: Mod -> View () () -> View dt () #

root :: Mod #

As layout but as a Mod

holygrail = col root $ do
  ...

grow :: Mod #

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

row id $ do
 el grow none
 el_ "Right"

collapse :: Mod #

Allow items to become smaller than their contents. This is not the opposite of grow!

scroll :: Mod #

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

A Nav element

type Application = Request -> (Response -> IO ResponseReceived) -> IO ResponseReceived #

The WAI application.

Note that, since WAI 3.0, this type is structured in continuation passing style to allow for proper safe resource handling. This was handled in the past via other means (e.g., ResourceT). As a demonstration:

app :: Application
app req respond = bracket_
    (putStrLn "Allocating scarce resource")
    (putStrLn "Cleaning up")
    (respond $ responseLBS status200 [] "Hello World")

run :: Port -> Application -> IO () #

Run an Application on the given port. This calls runSettings with defaultSettings.