atomic-css-0.1.0: Type-safe, composable CSS utility functions. Inspired by Tailwindcss and Elm-UI
Safe HaskellNone
LanguageGHC2021

Web.Atomic.Types.Style

Contents

Synopsis

Documentation

newtype Property Source #

Constructors

Property Text 

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

newtype Style Source #

Constructors

Style String 

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

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