Copyright | (c) 2023 Sean Hess |
---|---|
License | BSD3 |
Maintainer | Sean Hess <seanhess@gmail.com> |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | GHC2021 |
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 (context :: Type) = Attributes context -> Attributes context
- el :: Mod c -> View c () -> View c ()
- el_ :: View c () -> View c ()
- layout :: Mod c -> View c () -> View c ()
- root :: Mod c
- col :: Mod c -> View c () -> View c ()
- row :: Mod c -> View c () -> View c ()
- stack :: Mod c -> View c () -> View c ()
- grow :: Mod c
- space :: View c ()
- collapse :: Mod c
- scroll :: Mod c
- nav :: Mod c -> View c () -> View c ()
- text :: Text -> View c ()
- raw :: Text -> View c ()
- none :: View c ()
- pre :: Mod c -> Text -> View c ()
- form :: Mod c -> View c () -> View c ()
- input :: Mod c -> View c ()
- name :: Text -> Mod c
- value :: Text -> Mod c
- label :: Mod c -> View c () -> View c ()
- link :: Url -> Mod c -> View c () -> View c ()
- button :: Mod c -> View c () -> View c ()
- table :: Mod c -> [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 c -> 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 c
- height :: Length -> Mod c
- minWidth :: Length -> Mod c
- minHeight :: Length -> Mod c
- flexRow :: Mod c
- flexCol :: Mod c
- pad :: Sides Length -> Mod c
- gap :: Length -> Mod c
- hide :: Mod c
- opacity :: Float -> Mod c
- truncate :: Mod c
- shadow :: Mod c
- rounded :: Length -> Mod c
- fontSize :: Length -> Mod c
- color :: ToColor clr => clr -> Mod ctx
- bg :: ToColor clr => clr -> Mod ctx
- bold :: 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
- hover :: Mod c -> Mod c
- active :: Mod c -> Mod c
- even :: Mod c -> Mod c
- odd :: Mod c -> Mod c
- media :: Media -> Mod c -> Mod c
- parent :: Text -> Mod c -> Mod c
- context :: View context context
- addContext :: context -> View context () -> View c ()
- tag :: Text -> Mod c -> View c () -> View c ()
- att :: Name -> AttValue -> Mod c
- 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 View
s using composable Haskell functions
myView :: View ctx () 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 View
s
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 myView
module 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 context
or table
for an example
Mods
type Mod (context :: Type) = Attributes context -> Attributes context Source #
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"
Elements
Layout
layout :: Mod c -> View c () -> View c () Source #
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
col :: Mod c -> View c () -> View c () Source #
Lay out children in a column.
col grow $ do el_ "Top" space el_ "Bottom"
row :: Mod c -> View c () -> View c () Source #
Lay out children in a row
row id $ do el_ "Left" space el_ "Right"
stack :: Mod c -> View c () -> View c () Source #
Stack children on top of each other. Each child has the full width
stack id $ do row id "Background" row (bg Black . opacity 0.5) "Overlay"
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 c -> [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 #
data TableColumn c dt Source #
Document Metadata
stylesheet :: Text -> View c () Source #
CSS Modifiers
minWidth :: Length -> Mod c Source #
Allow width to grow to contents but not shrink any smaller than value
minHeight :: Length -> Mod c Source #
Allow height to grow to contents but not shrink any smaller than value
pad :: Sides Length -> Mod c 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 c 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 c Source #
Animate changes to the given property
el (transition 100 (Height 400)) "Tall" el (transition 100 (Height 100)) "Small"
Selector States
hover :: Mod c -> Mod c Source #
Apply when hovering over an element
el (bg Primary . hover (bg PrimaryLight)) "Hover"
media :: Media -> Mod c -> Mod c 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 c -> Mod c 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 #
Views have a Reader
built-in for convienient access to static data, and to add type-safety to view functions. See table
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 () Source #
Creating New Elements and Modifiers
tag :: Text -> Mod c -> View c () -> View c () Source #
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 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)
Instances
Media allows for responsive designs that change based on characteristics of the window. See Layout Example
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 Source # | |
Num PxRem Source # | |
Integral PxRem Source # | |
Real PxRem Source # | |
Defined in Web.View.Types toRational :: PxRem -> Rational # | |
Show PxRem Source # | |
Eq PxRem Source # | |
Ord PxRem Source # | |
ToClassName PxRem Source # | |
Defined in Web.View.Types toClassName :: PxRem -> ClassName Source # | |
ToStyleValue PxRem Source # | |
Defined in Web.View.Types toStyleValue :: PxRem -> StyleValue Source # |
Instances
Num Length Source # | |
Show Length Source # | |
ToClassName Length Source # | |
Defined in Web.View.Types toClassName :: Length -> ClassName Source # | |
ToStyleValue Length Source # | |
Defined in Web.View.Types toStyleValue :: Length -> StyleValue Source # |
data TransitionProperty Source #
Instances
Show TransitionProperty Source # | |
Defined in Web.View.Style 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 toClassName :: Ms -> ClassName Source # | |
ToStyleValue Ms Source # | |
Defined in Web.View.Types 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"
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 fromString :: String -> HexColor # | |
Show HexColor Source # | |
ToClassName HexColor Source # | |
Defined in Web.View.Types toClassName :: HexColor -> ClassName Source # | |
ToColor HexColor Source # | |
ToStyleValue HexColor Source # | |
Defined in Web.View.Types toStyleValue :: HexColor -> StyleValue Source # |
Instances
Show Align Source # | |
ToClassName Align Source # | |
Defined in Web.View.Types toClassName :: Align -> ClassName Source # | |
ToStyleValue Align Source # | |
Defined in Web.View.Types toStyleValue :: Align -> StyleValue Source # |
Url
module Web.View.Types.Url