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.CSS

Description

Type-safe Atomic CSS with composable css utility classes and intuitive layouts. Inspired by Tailwindcss and Elm-UI

import Web.Atomic

example = do
  el ~ flexCol . gap 10 $ do
    el ~ bold . fontSize 32 $ "My page"
    el "Hello!"

See Web.Atomic for a complete introduction

Synopsis

Atomic CSS

class Styleable h where Source #

Minimal complete definition

modCSS

Methods

(~) :: h -> (CSS h -> CSS h) -> h infixl 5 Source #

Apply a CSS utility to some html

el ~ bold . border 1 $ "styled"
el "styled" ~ bold . border 1
el "not styled"

Instances

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

Styleable [Rule] Source # 
Instance details

Defined in Web.Atomic.Types.Styleable

Methods

(~) :: [Rule] -> (CSS [Rule] -> CSS [Rule]) -> [Rule] Source #

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

Styleable (CSS h) Source # 
Instance details

Defined in Web.Atomic.Types.Styleable

Methods

(~) :: CSS h -> (CSS (CSS h) -> CSS (CSS h)) -> CSS h Source #

modCSS :: ([Rule] -> [Rule]) -> CSS h -> CSS h Source #

(Styleable a, Styleable b) => Styleable (a -> b) Source # 
Instance details

Defined in Web.Atomic.Types.Styleable

Methods

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

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

utility :: Styleable h => ClassName -> [Declaration] -> CSS h -> CSS h Source #

Create an atomic CSS utility. These are classes that set a single property, allowing you to compose styles like functions

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"

css :: Styleable h => ClassName -> Selector -> [Declaration] -> CSS h -> CSS h Source #

Embed CSS with a custom selector and apply it to an element. Modifiers like hover will ignore this

listItems =
  css
    "list"
    ".list > .item"
    [ "display" :. "list-item"
    , "list-style" :. "square"
    ]

example = do
  el ~ listItems $ do
    el ~ cls "item" $ "one"
    el ~ cls "item" $ "two"
    el ~ cls "item" $ "three"

cls :: Styleable h => ClassName -> CSS h -> CSS h Source #

Apply a class name with no styles. Useful for external CSS

el ~ cls "parent" $ do
  el ~ cls "item" $ "one"
  el ~ cls "item" $ "two"

CSS Utilities

Layout

display :: (PropertyStyle Display d, ToClassName d, Styleable h) => d -> CSS h -> CSS h Source #

Set container display

el ~ (display None) $ "none"
el ~ (display Block) $ "block"

data Display Source #

Constructors

Block 
Flex 

Instances

Instances details
ToClassName Display Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

ToStyle Display Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

Methods

style :: Display -> Style Source #

Show Display Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

PropertyStyle Display Display Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

PropertyStyle Display None Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

data Visibility Source #

Constructors

Visible 
Hidden 

Instances

Instances details
ToClassName Visibility Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

ToStyle Visibility Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

Show Visibility Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

PropertyStyle Overflow Visibility Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

width :: Styleable h => Length -> CSS h -> CSS h Source #

Set to specific width

el ~ width 100 $ "100px"
el ~ width (PxRem 100) $ "100px"
el ~ width (Pct 50) $ "50pct"

height :: Styleable h => Length -> CSS h -> CSS h Source #

minWidth :: Styleable h => Length -> CSS h -> CSS h Source #

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

minHeight :: Styleable h => Length -> CSS h -> CSS h Source #

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

position :: Styleable h => Position -> CSS h -> CSS h Source #

position:absolute, relative, etc. See stack and popup for a higher-level interface

tag "nav" ~ position Fixed . height 100 $ "Navigation bar"
tag "div" ~ flexCol . margin (T 100) $ "Main Content"

data Position Source #

Constructors

Absolute 
Fixed 
Sticky 
Relative 

Instances

Instances details
ToClassName Position Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

ToStyle Position Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

Methods

style :: Position -> Style Source #

Show Position Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

inset :: Styleable h => Sides Length -> CSS h -> CSS h Source #

Set top, bottom, right, and left all at once

top :: Styleable h => Length -> CSS h -> CSS h Source #

bottom :: Styleable h => Length -> CSS h -> CSS h Source #

right :: Styleable h => Length -> CSS h -> CSS h Source #

left :: Styleable h => Length -> CSS h -> CSS h Source #

overflow :: (PropertyStyle Overflow o, ToClassName o, Styleable h) => o -> CSS h -> CSS h Source #

Control how an element clips content that exceeds its bounds

Flexbox

We can intuitively create layouts by combining of flexRow, flexCol, grow, and stack

holygrail = do
  el ~ flexCol . grow $ do
    el ~ flexRow $ "Top Bar"
    el ~ flexRow . grow $ do
      el ~ flexCol $ "Left Sidebar"
      el ~ flexCol . grow $ "Main Content"
      el ~ flexCol $ "Right Sidebar"
    el ~ flexRow $ "Bottom Bar"

flexRow :: Styleable h => CSS h -> CSS h Source #

Lay out children in a row. See row

el ~ flexRow $ do
   el "Left"
   el " - " ~ grow
   el "Right"

flexCol :: Styleable h => CSS h -> CSS h Source #

Lay out children in a column. See col

el ~ flexCol $ do
   el "Top"
   el " - " ~ grow
   el "Bottom"

grow :: Styleable h => CSS h -> CSS h Source #

Grow to fill the available space in the parent flexRow or flexCol

data FlexDirection Source #

Constructors

Row 
Column 

Instances

Instances details
ToClassName FlexDirection Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

ToStyle FlexDirection Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

Show FlexDirection Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

flexWrap :: (PropertyStyle FlexWrap w, ToClassName w, Styleable h) => w -> CSS h -> CSS h Source #

Set the flex-wrap

el ~ flexWrap WrapReverse $ do
  el "one"
  el "two"
  el "three"
el ~ flexWrap Wrap $ do
  el "one"
  el "two"
  el "three"

data FlexWrap Source #

Constructors

WrapReverse 

Instances

Instances details
ToClassName FlexWrap Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

ToStyle FlexWrap Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

Methods

style :: FlexWrap -> Style Source #

Show FlexWrap Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

PropertyStyle FlexWrap FlexWrap Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

PropertyStyle FlexWrap Wrap Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

Window

zIndex :: Styleable h => Int -> CSS h -> CSS h Source #

Stack

stack :: Styleable h => CSS h -> CSS h Source #

Stack children on top of each other as layers. Each layer has the full width. See popup

el ~ stack $ do
  el "Background"
  el ~ bg Black . opacity 0.5 $ "Overlay"

popup :: Styleable h => Sides Length -> CSS h -> CSS h Source #

Place an element above others, out of the flow of the page

el ~ stack $ do
  input @ value "Autocomplete Box"
  el ~ popup (TL 10 10) $ do
    el "Item 1"
    el "Item 2"
    el "Item 3"
el "This would be covered by the menu"

Box Model

pad :: Styleable h => Sides Length -> CSS h -> CSS h Source #

Space surrounding the children of the element

To create even spacing around and between all elements combine with gap

el ~ flexCol . pad 10 . gap 10 $ do
  el "one"
  el "two"
  el "three"

gap :: Styleable h => Length -> CSS h -> CSS h Source #

The space between child elements. See pad

margin :: Styleable h => Sides Length -> CSS h -> CSS h Source #

Element margin. Using gap and pad on parents is more intuitive and usually makes margin redundant

bg :: (ToColor clr, Styleable h) => clr -> CSS h -> CSS h Source #

Set the background color. See ToColor

border :: Styleable h => Sides PxRem -> CSS h -> CSS h Source #

Set a border around the element

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

borderColor :: (ToColor clr, Styleable h) => clr -> CSS h -> CSS h Source #

Set a border color. See ToColor

data BorderStyle Source #

Constructors

Solid 
Dashed 

Instances

Instances details
ToClassName BorderStyle Source # 
Instance details

Defined in Web.Atomic.CSS.Box

ToStyle BorderStyle Source # 
Instance details

Defined in Web.Atomic.CSS.Box

Show BorderStyle Source # 
Instance details

Defined in Web.Atomic.CSS.Box

rounded :: Styleable h => Length -> CSS h -> CSS h Source #

Round the corners of the element

opacity :: Styleable h => Float -> CSS h -> CSS h Source #

shadow :: (Styleable h, PropertyStyle Shadow a, ToClassName a) => a -> CSS h -> CSS h Source #

Add a drop shadow to an element

input ~ shadow Inner $ "Inset Shadow"
button ~ shadow () $ "Click Me"

data Shadow Source #

Instances

Instances details
PropertyStyle Shadow Inner Source # 
Instance details

Defined in Web.Atomic.CSS.Box

PropertyStyle Shadow None Source # 
Instance details

Defined in Web.Atomic.CSS.Box

PropertyStyle Shadow () Source # 
Instance details

Defined in Web.Atomic.CSS.Box

Methods

propertyStyle :: () -> Style Source #

data Inner Source #

Constructors

Inner 

Instances

Instances details
ToClassName Inner Source # 
Instance details

Defined in Web.Atomic.CSS.Box

Show Inner Source # 
Instance details

Defined in Web.Atomic.CSS.Box

Methods

showsPrec :: Int -> Inner -> ShowS #

show :: Inner -> String #

showList :: [Inner] -> ShowS #

PropertyStyle Shadow Inner Source # 
Instance details

Defined in Web.Atomic.CSS.Box

Text

bold :: Styleable h => CSS h -> CSS h Source #

fontSize :: Styleable h => Length -> CSS h -> CSS h Source #

color :: (Styleable h, ToColor clr) => clr -> CSS h -> CSS h Source #

italic :: Styleable h => CSS h -> CSS h Source #

textAlign :: Styleable h => Align -> CSS h -> CSS h Source #

data Align Source #

Instances

Instances details
ToClassName Align Source # 
Instance details

Defined in Web.Atomic.CSS.Text

ToStyle Align Source # 
Instance details

Defined in Web.Atomic.CSS.Text

Methods

style :: Align -> Style Source #

Show Align Source # 
Instance details

Defined in Web.Atomic.CSS.Text

Methods

showsPrec :: Int -> Align -> ShowS #

show :: Align -> String #

showList :: [Align] -> ShowS #

data WhiteSpace Source #

Constructors

Pre 
PreWrap 
PreLine 
BreakSpaces 

Instances

Instances details
ToClassName WhiteSpace Source # 
Instance details

Defined in Web.Atomic.CSS.Text

ToStyle WhiteSpace Source # 
Instance details

Defined in Web.Atomic.CSS.Text

Show WhiteSpace Source # 
Instance details

Defined in Web.Atomic.CSS.Text

PropertyStyle WhiteSpace WhiteSpace Source # 
Instance details

Defined in Web.Atomic.CSS.Text

PropertyStyle WhiteSpace Normal Source # 
Instance details

Defined in Web.Atomic.CSS.Text

PropertyStyle WhiteSpace Wrap Source # 
Instance details

Defined in Web.Atomic.CSS.Text

CSS Transitions

transition :: Styleable h => Ms -> TransitionProperty -> CSS h -> CSS h Source #

Animate changes to the given property

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

Elements

list :: (ToClassName l, PropertyStyle ListType l, Styleable h) => l -> CSS h -> CSS h Source #

Set the list style of an item

tag "ol" $ do
  tag "li" ~ list Decimal $ "one"
  tag "li" ~ list Decimal $ "two"
  tag "li" ~ list Decimal $ "three"

data ListType Source #

Constructors

Decimal 
Disc 

Instances

Instances details
ToClassName ListType Source # 
Instance details

Defined in Web.Atomic.CSS

ToStyle ListType Source # 
Instance details

Defined in Web.Atomic.CSS

Methods

style :: ListType -> Style Source #

Show ListType Source # 
Instance details

Defined in Web.Atomic.CSS

PropertyStyle ListType ListType Source # 
Instance details

Defined in Web.Atomic.CSS

PropertyStyle ListType None Source # 
Instance details

Defined in Web.Atomic.CSS

pointer :: Styleable h => CSS h -> CSS h Source #

Use a button-like cursor when hovering over the element

Button-like elements:

btn = pointer . bg Primary . hover (bg PrimaryLight)

options = do
  el ~ btn $ "Login"
  el ~ btn $ "Sign Up"

Selector Modifiers

hover :: Styleable h => (CSS h -> CSS h) -> CSS h -> CSS h Source #

Apply when hovering over an element

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

active :: Styleable h => (CSS h -> CSS h) -> CSS h -> CSS h Source #

Apply when the mouse is pressed down on an element

even :: Styleable h => (CSS h -> CSS h) -> CSS h -> CSS h Source #

Apply to even-numbered children

odd :: Styleable h => (CSS h -> CSS h) -> CSS h -> CSS h Source #

Apply to odd-numbered children

descendentOf :: Styleable h => ClassName -> (CSS h -> CSS h) -> CSS h -> CSS h Source #

Apply when this element is contained somewhere another element with the given class

el ~ descendentOf "htmx-request" bold $ "Only bold when htmx is making a request"

media :: Styleable h => Media -> (CSS h -> CSS h) -> CSS h -> CSS h Source #

Apply when the Media matches the current window. This allows for responsive designs

el ~ width 100 . media (MinWidth 800) (width 400) $ do
  "Big if window > 800"

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

Defined in Web.Atomic.Types.Selector

Show Media Source # 
Instance details

Defined in Web.Atomic.Types.Selector

Methods

showsPrec :: Int -> Media -> ShowS #

show :: Media -> String #

showList :: [Media] -> ShowS #

Eq Media Source # 
Instance details

Defined in Web.Atomic.Types.Selector

Methods

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

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

Ord Media Source # 
Instance details

Defined in Web.Atomic.Types.Selector

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 #

Colors

class ToColor a where Source #

ToColor allows you to create a type containing your application's colors:

data AppColor
  = White
  | Primary
  | Dark
  deriving (Show)

instance ToColor AppColor where
  colorValue White = "#FFF"
  colorValue Dark = "#333"
  colorValue Primary = "#00F"

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.Atomic.Types.Style

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

Defined in Web.Atomic.Types.Style

ToColor HexColor Source # 
Instance details

Defined in Web.Atomic.Types.Style

ToStyle HexColor Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

style :: HexColor -> Style Source #

IsString HexColor Source # 
Instance details

Defined in Web.Atomic.Types.Style

Show HexColor Source # 
Instance details

Defined in Web.Atomic.Types.Style

CSS Reset

cssResetEmbed :: ByteString Source #

Default CSS to remove unintuitive default styles. This is required for utilities to work as expected

import Data.String.Interpolate (i)

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

Types

data Property Source #

Instances

Instances details
Semigroup Property Source # 
Instance details

Defined in Web.Atomic.Types.Style

IsString Property Source # 
Instance details

Defined in Web.Atomic.Types.Style

Show Property Source # 
Instance details

Defined in Web.Atomic.Types.Style

Eq Property Source # 
Instance details

Defined in Web.Atomic.Types.Style

Ord Property Source # 
Instance details

Defined in Web.Atomic.Types.Style

data Style Source #

Instances

Instances details
ToStyle Style Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

style :: Style -> Style Source #

Monoid Style Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

mempty :: Style #

mappend :: Style -> Style -> Style #

mconcat :: [Style] -> Style #

Semigroup Style Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

(<>) :: Style -> Style -> Style #

sconcat :: NonEmpty Style -> Style #

stimes :: Integral b => b -> Style -> Style #

IsString Style Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

fromString :: String -> Style #

Show Style Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

showsPrec :: Int -> Style -> ShowS #

show :: Style -> String #

showList :: [Style] -> ShowS #

Eq Style Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

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

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

Ord Style Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

compare :: Style -> Style -> Ordering #

(<) :: Style -> Style -> Bool #

(<=) :: Style -> Style -> Bool #

(>) :: Style -> Style -> Bool #

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

max :: Style -> Style -> Style #

min :: Style -> Style -> Style #

class ToStyle a where Source #

Convert a type to a css style value

data Float = Right | Left

instance ToStyle Float where
  style Right = "right"
  style Left = "left"

Minimal complete definition

Nothing

Methods

style :: a -> Style Source #

default style :: Show a => a -> Style Source #

Instances

Instances details
ToStyle ListType Source # 
Instance details

Defined in Web.Atomic.CSS

Methods

style :: ListType -> Style Source #

ToStyle BorderStyle Source # 
Instance details

Defined in Web.Atomic.CSS.Box

ToStyle Display Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

Methods

style :: Display -> Style Source #

ToStyle FlexDirection Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

ToStyle FlexWrap Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

Methods

style :: FlexWrap -> Style Source #

ToStyle Overflow Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

Methods

style :: Overflow -> Style Source #

ToStyle Position Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

Methods

style :: Position -> Style Source #

ToStyle Visibility Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

ToStyle Align Source # 
Instance details

Defined in Web.Atomic.CSS.Text

Methods

style :: Align -> Style Source #

ToStyle WhiteSpace Source # 
Instance details

Defined in Web.Atomic.CSS.Text

ToStyle Auto Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

style :: Auto -> Style Source #

ToStyle HexColor Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

style :: HexColor -> Style Source #

ToStyle Length Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

style :: Length -> Style Source #

ToStyle Ms Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

style :: Ms -> Style Source #

ToStyle None Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

style :: None -> Style Source #

ToStyle Normal Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

style :: Normal -> Style Source #

ToStyle PxRem Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

style :: PxRem -> Style Source #

ToStyle Style Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

style :: Style -> Style Source #

ToStyle Wrap Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

style :: Wrap -> Style Source #

ToStyle Text Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

style :: Text -> Style Source #

ToStyle String Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

style :: String -> Style Source #

ToStyle Float Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

style :: Float -> Style Source #

ToStyle Int Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

style :: Int -> Style Source #

class PropertyStyle (property :: k) value where Source #

Reuse types that belong to more than one css property

data None = None
  deriving (Show, ToClassName, ToStyle)

data Display
  = Block
  | Flex
  deriving (Show, ToClassName, ToStyle)
instance PropertyStyle Display Display
instance PropertyStyle Display None

display :: (PropertyStyle Display d, ToClassName d, Styleable h) => d -> CSS h -> CSS h
display disp =
  utility ("disp" -. disp) ["display" :. propertyStyle @Display disp]

Minimal complete definition

Nothing

Methods

propertyStyle :: value -> Style Source #

default propertyStyle :: ToStyle value => value -> Style Source #

Instances

Instances details
PropertyStyle ListType ListType Source # 
Instance details

Defined in Web.Atomic.CSS

PropertyStyle ListType None Source # 
Instance details

Defined in Web.Atomic.CSS

PropertyStyle Shadow Inner Source # 
Instance details

Defined in Web.Atomic.CSS.Box

PropertyStyle Shadow None Source # 
Instance details

Defined in Web.Atomic.CSS.Box

PropertyStyle Shadow () Source # 
Instance details

Defined in Web.Atomic.CSS.Box

Methods

propertyStyle :: () -> Style Source #

PropertyStyle Display Display Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

PropertyStyle Display None Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

PropertyStyle FlexWrap FlexWrap Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

PropertyStyle FlexWrap Wrap Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

PropertyStyle Overflow Overflow Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

PropertyStyle Overflow Visibility Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

PropertyStyle Overflow Auto Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

PropertyStyle WhiteSpace WhiteSpace Source # 
Instance details

Defined in Web.Atomic.CSS.Text

PropertyStyle WhiteSpace Normal Source # 
Instance details

Defined in Web.Atomic.CSS.Text

PropertyStyle WhiteSpace Wrap Source # 
Instance details

Defined in Web.Atomic.CSS.Text

data None Source #

Constructors

None 

Instances

Instances details
ToClassName None Source # 
Instance details

Defined in Web.Atomic.Types.Style

ToStyle None Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

style :: None -> Style Source #

Show None Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

showsPrec :: Int -> None -> ShowS #

show :: None -> String #

showList :: [None] -> ShowS #

PropertyStyle ListType None Source # 
Instance details

Defined in Web.Atomic.CSS

PropertyStyle Shadow None Source # 
Instance details

Defined in Web.Atomic.CSS.Box

PropertyStyle Display None Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

data Auto Source #

Constructors

Auto 

Instances

Instances details
ToClassName Auto Source # 
Instance details

Defined in Web.Atomic.Types.Style

ToStyle Auto Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

style :: Auto -> Style Source #

Show Auto Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

showsPrec :: Int -> Auto -> ShowS #

show :: Auto -> String #

showList :: [Auto] -> ShowS #

PropertyStyle Overflow Auto Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

data Normal Source #

Constructors

Normal 

Instances

Instances details
ToClassName Normal Source # 
Instance details

Defined in Web.Atomic.Types.Style

ToStyle Normal Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

style :: Normal -> Style Source #

Show Normal Source # 
Instance details

Defined in Web.Atomic.Types.Style

PropertyStyle WhiteSpace Normal Source # 
Instance details

Defined in Web.Atomic.CSS.Text

data Length Source #

Constructors

PxRem PxRem 
Pct Float 

Instances

Instances details
ToClassName Length Source # 
Instance details

Defined in Web.Atomic.Types.Style

ToStyle Length Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

style :: Length -> Style Source #

Num Length Source # 
Instance details

Defined in Web.Atomic.Types.Style

Show Length Source # 
Instance details

Defined in Web.Atomic.Types.Style

newtype 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

Constructors

PxRem' Int 

Instances

Instances details
ToClassName PxRem Source # 
Instance details

Defined in Web.Atomic.Types.Style

ToStyle PxRem Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

style :: PxRem -> Style Source #

Enum PxRem Source # 
Instance details

Defined in Web.Atomic.Types.Style

Num PxRem Source # 
Instance details

Defined in Web.Atomic.Types.Style

Integral PxRem Source # 
Instance details

Defined in Web.Atomic.Types.Style

Real PxRem Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

toRational :: PxRem -> Rational #

Show PxRem Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

showsPrec :: Int -> PxRem -> ShowS #

show :: PxRem -> String #

showList :: [PxRem] -> ShowS #

Eq PxRem Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

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

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

Ord PxRem Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

compare :: PxRem -> PxRem -> Ordering #

(<) :: PxRem -> PxRem -> Bool #

(<=) :: PxRem -> PxRem -> Bool #

(>) :: PxRem -> PxRem -> Bool #

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

max :: PxRem -> PxRem -> PxRem #

min :: PxRem -> PxRem -> PxRem #

newtype Ms Source #

Milliseconds, used for transitions

Constructors

Ms Int 

Instances

Instances details
ToClassName Ms Source # 
Instance details

Defined in Web.Atomic.Types.Style

ToStyle Ms Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

style :: Ms -> Style Source #

Num Ms Source # 
Instance details

Defined in Web.Atomic.Types.Style

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.Atomic.Types.Style

Methods

showsPrec :: Int -> Ms -> ShowS #

show :: Ms -> String #

showList :: [Ms] -> ShowS #

data Wrap Source #

Constructors

Wrap 
NoWrap 

Instances

Instances details
ToClassName Wrap Source # 
Instance details

Defined in Web.Atomic.Types.Style

ToStyle Wrap Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

style :: Wrap -> Style Source #

Show Wrap Source # 
Instance details

Defined in Web.Atomic.Types.Style

Methods

showsPrec :: Int -> Wrap -> ShowS #

show :: Wrap -> String #

showList :: [Wrap] -> ShowS #

PropertyStyle FlexWrap Wrap Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

PropertyStyle WhiteSpace Wrap Source # 
Instance details

Defined in Web.Atomic.CSS.Text

data Sides a Source #

Options for styles that support specifying various sides

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 
T a 
R a 
B a 
L a 
TR a a 
TL a a 
BR a a 
BL a a 

Instances

Instances details
Num a => Num (Sides a) Source # 
Instance details

Defined in Web.Atomic.Types.Style

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 CSS (h :: k) Source #

Instances

Instances details
Styleable (CSS h) Source # 
Instance details

Defined in Web.Atomic.Types.Styleable

Methods

(~) :: CSS h -> (CSS (CSS h) -> CSS (CSS h)) -> CSS h Source #

modCSS :: ([Rule] -> [Rule]) -> CSS h -> CSS h Source #

Monoid (CSS h) Source # 
Instance details

Defined in Web.Atomic.Types.Styleable

Methods

mempty :: CSS h #

mappend :: CSS h -> CSS h -> CSS h #

mconcat :: [CSS h] -> CSS h #

Semigroup (CSS h) Source # 
Instance details

Defined in Web.Atomic.Types.Styleable

Methods

(<>) :: CSS h -> CSS h -> CSS h #

sconcat :: NonEmpty (CSS h) -> CSS h #

stimes :: Integral b => b -> CSS h -> CSS h #

Other

declarations :: (CSS [Rule] -> CSS [Rule]) -> [Declaration] Source #

Get all the declarations for a utility or combination of them

rules :: (CSS [Rule] -> CSS [Rule]) -> [Rule] Source #

Get all the rules for combined utilities