Copyright | (c) 2023 Sean Hess |
---|---|
License | BSD3 |
Maintainer | Sean Hess <seanhess@gmail.com> |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | GHC2021 |
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 = doel
~flexCol
.gap
10 $ doel
~bold
.fontSize
32 $ "My page"el
"Hello!"
See Web.Atomic for a complete introduction
Synopsis
- class Styleable h where
- utility :: Styleable h => ClassName -> [Declaration] -> CSS h -> CSS h
- css :: Styleable h => ClassName -> Selector -> [Declaration] -> CSS h -> CSS h
- cls :: Styleable h => ClassName -> CSS h -> CSS h
- display :: (PropertyStyle Display d, ToClassName d, Styleable h) => d -> CSS h -> CSS h
- data Display
- visibility :: Styleable h => Visibility -> CSS h -> CSS h
- data Visibility
- width :: Styleable h => Length -> CSS h -> CSS h
- height :: Styleable h => Length -> CSS h -> CSS h
- minWidth :: Styleable h => Length -> CSS h -> CSS h
- minHeight :: Styleable h => Length -> CSS h -> CSS h
- position :: Styleable h => Position -> CSS h -> CSS h
- data Position
- inset :: Styleable h => Sides Length -> CSS h -> CSS h
- top :: Styleable h => Length -> CSS h -> CSS h
- bottom :: Styleable h => Length -> CSS h -> CSS h
- right :: Styleable h => Length -> CSS h -> CSS h
- left :: Styleable h => Length -> CSS h -> CSS h
- overflow :: (PropertyStyle Overflow o, ToClassName o, Styleable h) => o -> CSS h -> CSS h
- flexRow :: Styleable h => CSS h -> CSS h
- flexCol :: Styleable h => CSS h -> CSS h
- grow :: Styleable h => CSS h -> CSS h
- flexDirection :: Styleable h => FlexDirection -> CSS h -> CSS h
- data FlexDirection
- flexWrap :: (PropertyStyle FlexWrap w, ToClassName w, Styleable h) => w -> CSS h -> CSS h
- data FlexWrap = WrapReverse
- zIndex :: Styleable h => Int -> CSS h -> CSS h
- stack :: Styleable h => CSS h -> CSS h
- popup :: Styleable h => Sides Length -> CSS h -> CSS h
- pad :: Styleable h => Sides Length -> CSS h -> CSS h
- gap :: Styleable h => Length -> CSS h -> CSS h
- margin :: Styleable h => Sides Length -> CSS h -> CSS h
- bg :: (ToColor clr, Styleable h) => clr -> CSS h -> CSS h
- border :: Styleable h => Sides PxRem -> CSS h -> CSS h
- borderWidth :: Styleable h => Sides PxRem -> CSS h -> CSS h
- borderColor :: (ToColor clr, Styleable h) => clr -> CSS h -> CSS h
- borderStyle :: Styleable h => BorderStyle -> CSS h -> CSS h
- data BorderStyle
- rounded :: Styleable h => Length -> CSS h -> CSS h
- opacity :: Styleable h => Float -> CSS h -> CSS h
- shadow :: (Styleable h, PropertyStyle Shadow a, ToClassName a) => a -> CSS h -> CSS h
- data Shadow
- data Inner = Inner
- bold :: Styleable h => CSS h -> CSS h
- fontSize :: Styleable h => Length -> CSS h -> CSS h
- color :: (Styleable h, ToColor clr) => clr -> CSS h -> CSS h
- italic :: Styleable h => CSS h -> CSS h
- underline :: Styleable h => CSS h -> CSS h
- textAlign :: Styleable h => Align -> CSS h -> CSS h
- data Align
- whiteSpace :: (PropertyStyle WhiteSpace w, ToClassName w, Styleable h) => w -> CSS h -> CSS h
- data WhiteSpace
- = Pre
- | PreWrap
- | PreLine
- | BreakSpaces
- transition :: Styleable h => Ms -> TransitionProperty -> CSS h -> CSS h
- data TransitionProperty
- list :: (ToClassName l, PropertyStyle ListType l, Styleable h) => l -> CSS h -> CSS h
- data ListType
- pointer :: Styleable h => CSS h -> CSS h
- hover :: Styleable h => (CSS h -> CSS h) -> CSS h -> CSS h
- active :: Styleable h => (CSS h -> CSS h) -> CSS h -> CSS h
- even :: Styleable h => (CSS h -> CSS h) -> CSS h -> CSS h
- odd :: Styleable h => (CSS h -> CSS h) -> CSS h -> CSS h
- descendentOf :: Styleable h => ClassName -> (CSS h -> CSS h) -> CSS h -> CSS h
- media :: Styleable h => Media -> (CSS h -> CSS h) -> CSS h -> CSS h
- data Media
- class ToColor a where
- colorValue :: a -> HexColor
- colorName :: a -> Text
- newtype HexColor = HexColor Text
- cssResetEmbed :: ByteString
- data Property
- data Declaration = Property :. Style
- data Style
- class ToStyle a where
- class PropertyStyle (property :: k) value where
- propertyStyle :: value -> Style
- data None = None
- data Auto = Auto
- data Normal = Normal
- data Length
- newtype PxRem = PxRem' Int
- newtype Ms = Ms Int
- data Wrap
- data Sides a
- data CSS (h :: k)
- declarations :: (CSS [Rule] -> CSS [Rule]) -> [Declaration]
- rules :: (CSS [Rule] -> CSS [Rule]) -> [Rule]
Atomic CSS
class Styleable h where Source #
Minimal complete definition
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"
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 #
Instances
ToClassName Display Source # | |
Defined in Web.Atomic.CSS.Layout Methods toClassName :: Display -> ClassName Source # | |
ToStyle Display Source # | |
Show Display Source # | |
PropertyStyle Display Display Source # | |
Defined in Web.Atomic.CSS.Layout Methods propertyStyle :: Display -> Style Source # | |
PropertyStyle Display None Source # | |
Defined in Web.Atomic.CSS.Layout Methods propertyStyle :: None -> Style Source # |
visibility :: Styleable h => Visibility -> CSS h -> CSS h Source #
data Visibility Source #
Instances
ToClassName Visibility Source # | |
Defined in Web.Atomic.CSS.Layout Methods toClassName :: Visibility -> ClassName Source # | |
ToStyle Visibility Source # | |
Defined in Web.Atomic.CSS.Layout Methods style :: Visibility -> Style Source # | |
Show Visibility Source # | |
Defined in Web.Atomic.CSS.Layout Methods showsPrec :: Int -> Visibility -> ShowS # show :: Visibility -> String # showList :: [Visibility] -> ShowS # | |
PropertyStyle Overflow Visibility Source # | |
Defined in Web.Atomic.CSS.Layout Methods propertyStyle :: Visibility -> Style Source # |
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"
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
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"
flexDirection :: Styleable h => FlexDirection -> CSS h -> CSS h Source #
data FlexDirection Source #
Instances
ToClassName FlexDirection Source # | |
Defined in Web.Atomic.CSS.Layout Methods toClassName :: FlexDirection -> ClassName Source # | |
ToStyle FlexDirection Source # | |
Defined in Web.Atomic.CSS.Layout Methods style :: FlexDirection -> Style Source # | |
Show FlexDirection Source # | |
Defined in Web.Atomic.CSS.Layout Methods showsPrec :: Int -> FlexDirection -> ShowS # show :: FlexDirection -> String # showList :: [FlexDirection] -> ShowS # |
flexWrap :: (PropertyStyle FlexWrap w, ToClassName w, Styleable h) => w -> CSS h -> CSS h Source #
Set the flex-wrap
el ~ flexWrapWrapReverse
$ do el "one" el "two" el "three" el ~ flexWrapWrap
$ do el "one" el "two" el "three"
Constructors
WrapReverse |
Instances
ToClassName FlexWrap Source # | |
Defined in Web.Atomic.CSS.Layout Methods toClassName :: FlexWrap -> ClassName Source # | |
ToStyle FlexWrap Source # | |
Show FlexWrap Source # | |
PropertyStyle FlexWrap FlexWrap Source # | |
Defined in Web.Atomic.CSS.Layout Methods propertyStyle :: FlexWrap -> Style Source # | |
PropertyStyle FlexWrap Wrap Source # | |
Defined in Web.Atomic.CSS.Layout Methods propertyStyle :: Wrap -> Style Source # |
Window
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"
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
borderStyle :: Styleable h => BorderStyle -> CSS h -> CSS h Source #
data BorderStyle Source #
Instances
ToClassName BorderStyle Source # | |
Defined in Web.Atomic.CSS.Box Methods toClassName :: BorderStyle -> ClassName Source # | |
ToStyle BorderStyle Source # | |
Defined in Web.Atomic.CSS.Box Methods style :: BorderStyle -> Style Source # | |
Show BorderStyle Source # | |
Defined in Web.Atomic.CSS.Box Methods showsPrec :: Int -> BorderStyle -> ShowS # show :: BorderStyle -> String # showList :: [BorderStyle] -> ShowS # |
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"
Instances
PropertyStyle Shadow Inner Source # | |
Defined in Web.Atomic.CSS.Box Methods propertyStyle :: Inner -> Style Source # | |
PropertyStyle Shadow None Source # | |
Defined in Web.Atomic.CSS.Box Methods propertyStyle :: None -> Style Source # | |
PropertyStyle Shadow () Source # | |
Defined in Web.Atomic.CSS.Box Methods propertyStyle :: () -> Style Source # |
Constructors
Inner |
Instances
ToClassName Inner Source # | |
Defined in Web.Atomic.CSS.Box Methods toClassName :: Inner -> ClassName Source # | |
Show Inner Source # | |
PropertyStyle Shadow Inner Source # | |
Defined in Web.Atomic.CSS.Box Methods propertyStyle :: Inner -> Style Source # |
Text
Constructors
AlignCenter | |
AlignLeft | |
AlignRight | |
AlignJustify |
whiteSpace :: (PropertyStyle WhiteSpace w, ToClassName w, Styleable h) => w -> CSS h -> CSS h Source #
data WhiteSpace Source #
Constructors
Pre | |
PreWrap | |
PreLine | |
BreakSpaces |
Instances
ToClassName WhiteSpace Source # | |
Defined in Web.Atomic.CSS.Text Methods toClassName :: WhiteSpace -> ClassName Source # | |
ToStyle WhiteSpace Source # | |
Defined in Web.Atomic.CSS.Text Methods style :: WhiteSpace -> Style Source # | |
Show WhiteSpace Source # | |
Defined in Web.Atomic.CSS.Text Methods showsPrec :: Int -> WhiteSpace -> ShowS # show :: WhiteSpace -> String # showList :: [WhiteSpace] -> ShowS # | |
PropertyStyle WhiteSpace WhiteSpace Source # | |
Defined in Web.Atomic.CSS.Text Methods propertyStyle :: WhiteSpace -> Style Source # | |
PropertyStyle WhiteSpace Normal Source # | |
Defined in Web.Atomic.CSS.Text Methods propertyStyle :: Normal -> Style Source # | |
PropertyStyle WhiteSpace Wrap Source # | |
Defined in Web.Atomic.CSS.Text Methods propertyStyle :: Wrap -> Style Source # |
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"
data TransitionProperty Source #
Instances
Show TransitionProperty Source # | |
Defined in Web.Atomic.CSS.Transition Methods showsPrec :: Int -> TransitionProperty -> ShowS # show :: TransitionProperty -> String # showList :: [TransitionProperty] -> ShowS # |
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"
Instances
ToClassName ListType Source # | |
Defined in Web.Atomic.CSS Methods toClassName :: ListType -> ClassName Source # | |
ToStyle ListType Source # | |
Show ListType Source # | |
PropertyStyle ListType ListType Source # | |
Defined in Web.Atomic.CSS Methods propertyStyle :: ListType -> Style Source # | |
PropertyStyle ListType None Source # | |
Defined in Web.Atomic.CSS Methods propertyStyle :: None -> Style Source # |
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
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"
Media allows for responsive designs that change based on characteristics of the window. See Layout Example
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
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
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 Declaration Source #
Instances
Show Declaration Source # | |
Defined in Web.Atomic.Types.Style Methods showsPrec :: Int -> Declaration -> ShowS # show :: Declaration -> String # showList :: [Declaration] -> ShowS # | |
Eq Declaration Source # | |
Defined in Web.Atomic.Types.Style | |
Ord Declaration Source # | |
Defined in Web.Atomic.Types.Style Methods compare :: Declaration -> Declaration -> Ordering # (<) :: Declaration -> Declaration -> Bool # (<=) :: Declaration -> Declaration -> Bool # (>) :: Declaration -> Declaration -> Bool # (>=) :: Declaration -> Declaration -> Bool # max :: Declaration -> Declaration -> Declaration # min :: Declaration -> Declaration -> Declaration # |
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
Instances
ToStyle ListType Source # | |
ToStyle BorderStyle Source # | |
Defined in Web.Atomic.CSS.Box Methods style :: BorderStyle -> Style Source # | |
ToStyle Display Source # | |
ToStyle FlexDirection Source # | |
Defined in Web.Atomic.CSS.Layout Methods style :: FlexDirection -> Style Source # | |
ToStyle FlexWrap Source # | |
ToStyle Overflow Source # | |
ToStyle Position Source # | |
ToStyle Visibility Source # | |
Defined in Web.Atomic.CSS.Layout Methods style :: Visibility -> Style Source # | |
ToStyle Align Source # | |
ToStyle WhiteSpace Source # | |
Defined in Web.Atomic.CSS.Text Methods style :: WhiteSpace -> Style Source # | |
ToStyle Auto Source # | |
ToStyle HexColor Source # | |
ToStyle Length Source # | |
ToStyle Ms Source # | |
ToStyle None Source # | |
ToStyle Normal Source # | |
ToStyle PxRem Source # | |
ToStyle Style Source # | |
ToStyle Wrap Source # | |
ToStyle Text Source # | |
ToStyle String Source # | |
ToStyle Float Source # | |
ToStyle Int 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
Constructors
None |
Instances
ToClassName None Source # | |
Defined in Web.Atomic.Types.Style Methods toClassName :: None -> ClassName Source # | |
ToStyle None Source # | |
Show None Source # | |
PropertyStyle ListType None Source # | |
Defined in Web.Atomic.CSS Methods propertyStyle :: None -> Style Source # | |
PropertyStyle Shadow None Source # | |
Defined in Web.Atomic.CSS.Box Methods propertyStyle :: None -> Style Source # | |
PropertyStyle Display None Source # | |
Defined in Web.Atomic.CSS.Layout Methods propertyStyle :: None -> Style Source # |
Constructors
Auto |
Instances
ToClassName Auto Source # | |
Defined in Web.Atomic.Types.Style Methods toClassName :: Auto -> ClassName Source # | |
ToStyle Auto Source # | |
Show Auto Source # | |
PropertyStyle Overflow Auto Source # | |
Defined in Web.Atomic.CSS.Layout Methods propertyStyle :: Auto -> Style Source # |
Constructors
Normal |
Instances
ToClassName Normal Source # | |
Defined in Web.Atomic.Types.Style Methods toClassName :: Normal -> ClassName Source # | |
ToStyle Normal Source # | |
Show Normal Source # | |
PropertyStyle WhiteSpace Normal Source # | |
Defined in Web.Atomic.CSS.Text Methods propertyStyle :: Normal -> Style 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
Instances
ToClassName PxRem Source # | |
Defined in Web.Atomic.Types.Style Methods toClassName :: PxRem -> ClassName Source # | |
ToStyle PxRem Source # | |
Enum PxRem Source # | |
Defined in Web.Atomic.Types.Style | |
Num PxRem Source # | |
Integral PxRem Source # | |
Real PxRem Source # | |
Defined in Web.Atomic.Types.Style Methods toRational :: PxRem -> Rational # | |
Show PxRem Source # | |
Eq PxRem Source # | |
Ord PxRem Source # | |
Milliseconds, used for transitions
Instances
ToClassName Wrap Source # | |
Defined in Web.Atomic.Types.Style Methods toClassName :: Wrap -> ClassName Source # | |
ToStyle Wrap Source # | |
Show Wrap Source # | |
PropertyStyle FlexWrap Wrap Source # | |
Defined in Web.Atomic.CSS.Layout Methods propertyStyle :: Wrap -> Style Source # | |
PropertyStyle WhiteSpace Wrap Source # | |
Defined in Web.Atomic.CSS.Text Methods propertyStyle :: Wrap -> Style Source # |
Options for styles that support specifying various sides
border 5 border (X 2) border (TRBL 0 5 0 0)
Other
declarations :: (CSS [Rule] -> CSS [Rule]) -> [Declaration] Source #
Get all the declarations for a utility or combination of them