web-view-0.3.1: Type-safe HTML and CSS with intuitive layouts and composable styles.
Copyright(c) 2023 Sean Hess
LicenseBSD3
MaintainerSean Hess <seanhess@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageGHC2021

Web.View

Description

Type-safe HTML and CSS with intuitive layout and composable styles. Inspired by Tailwindcss and Elm-UI

Synopsis

How to use this library

Create styled Views using composable Haskell functions

myView :: View c ()
myView = col (gap 10) $ do
 el (bold . fontSize 32) "My page"
 button (border 1) "Click Me"

This represents an HTML fragment with embedded CSS definitions

<style type='text/css'>
.bold { font-weight:bold }
.brd-1 { border:1px; border-style:solid }
.col { display:flex; flex-direction:column }
.fs-32 { font-size:2.0rem }
.gap-10 { gap:0.625rem }
</style>

<div class='col gap-10'>
  <div class='bold fs-32'>My page</div>
  <button class='brd-1'>Click Me</button>
</div>

Leverage the full power of Haskell functions for reuse, instead of relying on CSS.

header = bold
h1 = header . fontSize 32
h2 = header . fontSize 24
page = gap 10

myView = col page $ do
  el h1 "My Page"
...

This approach is inspired by Tailwindcss' Utility Classes

Rendering Views

renderText :: View () () -> Text Source #

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>

Full HTML Documents

Create a full HTML document by embedding the view and cssResetEmbed

import Data.String.Interpolate (i)
import Web.View

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

myDocument :: Text
myDocument = toDocument $ renderText myView

Views

data View context a Source #

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

Defined in Web.View.View

Methods

fromString :: String -> View context () #

Mods

type Mod = Attributes -> Attributes Source #

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

Elements

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

A basic element

el (bold . pad 10) "Hello"

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

A basic element, with no modifiers

el_ "Hello"

Layout

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

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

root :: Mod Source #

As layout but as a Mod

holygrail = col root $ do
  ...

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

Lay out children in a column.

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

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

Lay out children in a row

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

grow :: Mod Source #

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

row id $ do
 el grow none
 el_ "Right"

space :: View c () Source #

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

collapse :: Mod Source #

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

scroll :: Mod Source #

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

A Nav element

Content

text :: Text -> View c () Source #

Add text to a view. Not required for string literals

el_ $ do
  "Hello: "
  text user.name

raw :: Text -> View c () Source #

Embed static, unescaped HTML or SVG. Take care not to use raw with user-generated content.

spinner = raw "<svg>...</svg>"

none :: View c () Source #

Do not show any content

if isVisible
 then content
 else none

pre :: Mod -> Text -> View c () Source #

Inputs

form :: Mod -> View c () -> View c () Source #

input :: Mod -> View c () Source #

label :: Mod -> View c () -> View c () Source #

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

A hyperlink to the given url

button :: Mod -> View c () -> View c () Source #

Tables

table :: Mod -> [dt] -> Eff '[Writer [TableColumn c dt]] () -> View c () Source #

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

tcol :: forall dt c. View (TableHead c) () -> (dt -> View dt ()) -> Eff '[Writer [TableColumn c dt]] () Source #

th :: Mod -> View c () -> View (TableHead c) () Source #

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

Document Metadata

script :: Text -> View c () Source #

style :: Text -> View c () Source #

CSS Modifiers

width :: PxRem -> Mod Source #

Set to a specific width

height :: PxRem -> Mod Source #

Set to a specific height

minWidth :: PxRem -> Mod Source #

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

minHeight :: PxRem -> Mod Source #

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

flexRow :: Mod Source #

Set container to be a row. Favor row when possible

flexCol :: Mod Source #

Set container to be a column. Favor col when possible

pad :: Sides PxRem -> Mod Source #

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"

gap :: PxRem -> Mod Source #

The space between child elements. See pad

hide :: Mod Source #

Hide an element. See parent and media

shadow :: Mod Source #

Adds a basic drop shadow to an element

rounded :: PxRem -> Mod Source #

Round the corners of the element

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

Set the text color. See ToColor

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

Set the background color. See ToColor

border :: Sides PxRem -> Mod Source #

Set a border around the element

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

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

Set a border color. See ToColor

pointer :: Mod Source #

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

Animate changes to the given property

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

Selector States

hover :: Mod -> Mod Source #

Apply when hovering over an element

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

active :: Mod -> Mod Source #

Apply when the mouse is pressed down on an element

even :: Mod -> Mod Source #

Apply to even-numbered children

odd :: Mod -> Mod Source #

Apply to odd-numbered children

media :: Media -> Mod -> Mod Source #

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

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"

View Context

context :: View context context Source #

Get the current context

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

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

Creating New Elements and Modifiers

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

Create a new element constructor

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

att :: Name -> AttValue -> Mod Source #

Set an attribute, replacing existing value

hlink :: Text -> View c () -> View c ()
hlink url content = tag "a" (att "href" url) content

Types

data Sides a Source #

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

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 Source # 
Instance details

Defined in Web.View.Types

Methods

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

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

Ord Media Source # 
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 PxRem 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

Instances details
Num PxRem Source # 
Instance details

Defined in Web.View.Types

Show PxRem Source # 
Instance details

Defined in Web.View.Types

Methods

showsPrec :: Int -> PxRem -> ShowS #

show :: PxRem -> String #

showList :: [PxRem] -> ShowS #

ToClassName PxRem Source # 
Instance details

Defined in Web.View.Types

ToStyleValue PxRem Source # 
Instance details

Defined in Web.View.Types

newtype Url Source #

Constructors

Url Text 

Instances

Instances details
IsString Url Source # 
Instance details

Defined in Web.View.Types

Methods

fromString :: String -> Url #

data TransitionProperty Source #

Constructors

Width PxRem 
Height PxRem 

Instances

Instances details
Show TransitionProperty Source # 
Instance details

Defined in Web.View.Style

data Ms Source #

Milliseconds, used for transitions

Instances

Instances details
Num Ms Source # 
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 Source # 
Instance details

Defined in Web.View.Types

Methods

showsPrec :: Int -> Ms -> ShowS #

show :: Ms -> String #

showList :: [Ms] -> ShowS #

ToClassName Ms Source # 
Instance details

Defined in Web.View.Types

Methods

toClassName :: Ms -> Text Source #

ToStyleValue Ms Source # 
Instance details

Defined in Web.View.Types

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"

Minimal complete definition

colorValue

Methods

colorValue :: a -> HexColor Source #

colorName :: a -> Text Source #

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

Instances

Instances details
ToColor HexColor Source # 
Instance details

Defined in Web.View.Types

newtype 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

Constructors

HexColor Text 

Instances

Instances details
IsString HexColor Source # 
Instance details

Defined in Web.View.Types

ToColor HexColor Source # 
Instance details

Defined in Web.View.Types

ToStyleValue HexColor Source # 
Instance details

Defined in Web.View.Types