atomic-css-0.1.0: Type-safe, composable CSS utility functions. Inspired by Tailwindcss and Elm-UI
Copyright(c) 2023 Sean Hess
LicenseBSD3
MaintainerSean Hess <seanhess@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageGHC2021

Web.Atomic

Description

Type-safe, composable CSS utility functions. Inspired by Tailwindcss and Elm-UI

Synopsis

Haskell functions instead of classes

Style your html with composable CSS utility functions:

el ~ bold . pad 8 $ "Hello World"

This renders as the following HTML with embedded CSS utility classes:

<style type='text/css'>
.bold { font-weight:bold }
.p-8 { padding:0.500rem }
</style>

<div class='bold p-8'>Hello World</div>

Instead of relying on the fickle cascade for code reuse, factor and compose styles with the full power of Haskell functions!

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

example = el ~ page $ do
  el ~ h1 $ "My Page"
  el ~ h2 $ "Introduction"
  el "lorem ipsum..."

This approach is inspired by Tailwindcss' Utility Classes

Atomic CSS

The main purpose of atomic-css is to provide CSS Utilities and the (~) operator to style HTML. These utilities can be used by any combinator library. See Hyperbole

bold :: Styleable h => CSS h -> CSS h
bold = utility "bold" ["font-weight" :. "bold"]

pad :: Styleable h => PxRem -> CSS h -> CSS h
pad px = utility ("pad" -. px) ["padding" :. style px]

example = el ~ bold . pad 10 $ "Padded and bold"

Web.Atomic.CSS contains many useful utilities:

Html Monad

Atomic-css also provides an Html Monad and combinator library with basic functions to generate html and add attributes with the (@) operator

data Html a Source #

Html monad

import Web.Atomic

example = do
  el ~ pad 10 $ do
    el ~ fontSize 24 . bold $ "My Links"
    a @ href "hoogle.haskell.org" ~ link $ "Hoogle"
    a @ href "hackage.haskell.org" ~ link $ "Hackage"

link = underline . color Primary
a = tag "a"
href = att "href"

Instances

Instances details
Applicative Html Source # 
Instance details

Defined in Web.Atomic.Html

Methods

pure :: a -> Html a #

(<*>) :: Html (a -> b) -> Html a -> Html b #

liftA2 :: (a -> b -> c) -> Html a -> Html b -> Html c #

(*>) :: Html a -> Html b -> Html b #

(<*) :: Html a -> Html b -> Html a #

Functor Html Source # 
Instance details

Defined in Web.Atomic.Html

Methods

fmap :: (a -> b) -> Html a -> Html b #

(<$) :: a -> Html b -> Html a #

Monad Html Source # 
Instance details

Defined in Web.Atomic.Html

Methods

(>>=) :: Html a -> (a -> Html b) -> Html b #

(>>) :: Html a -> Html b -> Html b #

return :: a -> Html a #

Attributable (Html a) Source # 
Instance details

Defined in Web.Atomic.Html

Styleable (Html a) Source # 
Instance details

Defined in Web.Atomic.Html

Methods

(~) :: Html a -> (CSS (Html a) -> CSS (Html a)) -> Html a Source #

modCSS :: ([Rule] -> [Rule]) -> Html a -> Html a Source #

IsString (Html ()) Source # 
Instance details

Defined in Web.Atomic.Html

Methods

fromString :: String -> Html () #

IsList (Html ()) Source # 
Instance details

Defined in Web.Atomic.Html

Associated Types

type Item (Html ()) 
Instance details

Defined in Web.Atomic.Html

type Item (Html ()) = Node

Methods

fromList :: [Item (Html ())] -> Html () #

fromListN :: Int -> [Item (Html ())] -> Html () #

toList :: Html () -> [Item (Html ())] #

type Item (Html ()) Source # 
Instance details

Defined in Web.Atomic.Html

type Item (Html ()) = Node

el :: Html () -> Html () Source #

tag :: Text -> Html () -> Html () Source #

raw :: Text -> Html () Source #

text :: Text -> Html () Source #

Layout

Rendering