| Copyright | (c) 2023 Sean Hess |
|---|---|
| License | BSD3 |
| Maintainer | Sean Hess <seanhess@gmail.com> |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | Safe-Inferred |
| Language | GHC2021 |
Web.View
Description
Type-safe HTML and CSS with intuitive layout and composable styles. Inspired by Tailwindcss and Elm-UI
Synopsis
- renderText :: View () () -> Text
- renderLazyText :: View () () -> Text
- renderLazyByteString :: View () () -> ByteString
- module Web.View.Reset
- data View context a
- type Mod = Attributes -> Attributes
- el :: Mod -> View c () -> View c ()
- el_ :: View c () -> View c ()
- layout :: Mod -> View c () -> View c ()
- root :: Mod
- col :: Mod -> View c () -> View c ()
- row :: Mod -> View c () -> View c ()
- grow :: Mod
- space :: View c ()
- collapse :: Mod
- scroll :: Mod
- nav :: Mod -> View c () -> View c ()
- text :: Text -> View c ()
- raw :: Text -> View c ()
- none :: View c ()
- pre :: Mod -> Text -> View c ()
- form :: Mod -> View c () -> View c ()
- input :: Mod -> View c ()
- name :: Text -> Mod
- value :: Text -> Mod
- label :: Mod -> View c () -> View c ()
- link :: Url -> Mod -> View c () -> View c ()
- button :: Mod -> View c () -> View c ()
- table :: Mod -> [dt] -> Eff '[Writer [TableColumn c dt]] () -> 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 ()
- data TableHead a
- data TableColumn c dt
- script :: Text -> View c ()
- style :: Text -> View c ()
- stylesheet :: Text -> View c ()
- width :: Length -> Mod
- height :: Length -> Mod
- minWidth :: Length -> Mod
- minHeight :: Length -> Mod
- flexRow :: Mod
- flexCol :: Mod
- pad :: Sides Length -> Mod
- gap :: Length -> Mod
- hide :: Mod
- opacity :: Float -> Mod
- truncate :: Mod
- shadow :: Mod
- rounded :: Length -> Mod
- fontSize :: Length -> Mod
- color :: ToColor c => c -> Mod
- bg :: ToColor c => c -> Mod
- bold :: Mod
- border :: Sides PxRem -> Mod
- borderColor :: ToColor c => c -> Mod
- pointer :: Mod
- transition :: Ms -> TransitionProperty -> Mod
- textAlign :: Align -> Mod
- hover :: Mod -> Mod
- active :: Mod -> Mod
- even :: Mod -> Mod
- odd :: Mod -> Mod
- media :: Media -> Mod -> Mod
- parent :: Text -> Mod -> Mod
- context :: View context context
- addContext :: context -> View context () -> View c ()
- tag :: Text -> Mod -> View c () -> View c ()
- att :: Name -> AttValue -> Mod
- data Sides a
- data Media
- data PxRem
- data Length
- data TransitionProperty
- data Ms
- class ToColor a where
- colorValue :: a -> HexColor
- colorName :: a -> Text
- newtype HexColor = HexColor Text
- data Align = Center
- module Web.View.Types.Url
- type Query = [QueryItem]
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>
renderLazyText :: View () () -> Text Source #
renderLazyByteString :: View () () -> ByteString Source #
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 myViewmodule Web.View.Reset
Views
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
| Applicative (View context) Source # | |
| Functor (View context) Source # | |
| Monad (View context) Source # | |
| IsString (View context ()) Source # | |
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 idElements
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 ::Viewc () holygrail =layoutid $ dorowsection "Top Bar"rowgrow$ docolsection "Left Sidebar"col(section .grow) "Main Content"colsection "Right Sidebar"rowsection "Bottom Bar" where section =border1
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"
Allow items to become smaller than their contents. This is not the opposite of grow!
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>"
Inputs
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 1tcol :: forall dt c. View (TableHead c) () -> (dt -> View dt ()) -> Eff '[Writer [TableColumn c dt]] () Source #
data TableColumn c dt Source #
Document Metadata
stylesheet :: Text -> View c () Source #
CSS Modifiers
minWidth :: Length -> Mod Source #
Allow width to grow to contents but not shrink any smaller than value
minHeight :: Length -> Mod Source #
Allow height to grow to contents but not shrink any smaller than value
pad :: Sides Length -> 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"
border :: Sides PxRem -> Mod Source #
Set a border around the element
el (border 1) "all sides" el (border (X 1)) "only left and right"
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
Apply when hovering over an element
el (bg Primary . hover (bg PrimaryLight)) "Hover"
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
addContext :: context -> View context () -> View c () Source #
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
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)
Media allows for responsive designs that change based on characteristics of the window. See Layout Example
Instances
| Enum PxRem Source # | |
| Num PxRem Source # | |
| Integral PxRem Source # | |
| Real PxRem Source # | |
Defined in Web.View.Types Methods toRational :: PxRem -> Rational # | |
| Show PxRem Source # | |
| Eq PxRem Source # | |
| Ord PxRem Source # | |
| ToClassName PxRem Source # | |
Defined in Web.View.Types Methods toClassName :: PxRem -> Text Source # | |
| ToStyleValue PxRem Source # | |
Defined in Web.View.Types Methods toStyleValue :: PxRem -> StyleValue Source # | |
Constructors
| PxRem 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 |
| Pct Float |
Instances
| Num Length Source # | |
| Show Length Source # | |
| ToClassName Length Source # | |
Defined in Web.View.Types Methods toClassName :: Length -> Text Source # | |
| ToStyleValue Length Source # | |
Defined in Web.View.Types Methods toStyleValue :: Length -> StyleValue Source # | |
data TransitionProperty Source #
Instances
| Show TransitionProperty Source # | |
Defined in Web.View.Style Methods showsPrec :: Int -> TransitionProperty -> ShowS # show :: TransitionProperty -> String # showList :: [TransitionProperty] -> ShowS # | |
Milliseconds, used for transitions
Instances
| Num Ms Source # | |
| Show Ms Source # | |
| ToClassName Ms Source # | |
Defined in Web.View.Types Methods toClassName :: Ms -> Text Source # | |
| ToStyleValue Ms Source # | |
Defined in Web.View.Types Methods toStyleValue :: Ms -> StyleValue Source # | |
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
Methods
colorValue :: a -> 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
Instances
| IsString HexColor Source # | |
Defined in Web.View.Types Methods fromString :: String -> HexColor # | |
| ToColor HexColor Source # | |
| ToStyleValue HexColor Source # | |
Defined in Web.View.Types Methods toStyleValue :: HexColor -> StyleValue Source # | |
Constructors
| Center |
Instances
| Show Align Source # | |
| ToClassName Align Source # | |
Defined in Web.View.Types Methods toClassName :: Align -> Text Source # | |
| ToStyleValue Align Source # | |
Defined in Web.View.Types Methods toStyleValue :: Align -> StyleValue Source # | |
Url
module Web.View.Types.Url