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

Description

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"

Also see col, row, and space

Synopsis

Documentation

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"

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"

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

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

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"

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 #

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

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

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"

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

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

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

data Overflow Source #

Constructors

Scroll 
Clip 

Instances

Instances details
ToClassName Overflow Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

ToStyle Overflow Source # 
Instance details

Defined in Web.Atomic.CSS.Layout

Methods

style :: Overflow -> Style Source #

Show Overflow 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

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

Control how an element clips content that exceeds its bounds