Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- width :: Length -> Mod c
- height :: Length -> Mod c
- minWidth :: Length -> Mod c
- minHeight :: Length -> Mod c
- pad :: Sides Length -> Mod c
- gap :: Length -> Mod c
- fontSize :: Length -> Mod c
- shadow :: (Style Shadow a, ToClassName a) => a -> Mod c
- data Shadow
- data Inner = Inner
- rounded :: Length -> Mod c
- bg :: ToColor clr => clr -> Mod ctx
- color :: ToColor clr => clr -> Mod ctx
- bold :: Mod c
- italic :: Mod c
- underline :: Mod c
- list :: (ToClassName a, Style ListType a) => a -> Mod c
- data ListType
- opacity :: Float -> Mod c
- border :: Sides PxRem -> Mod c
- borderColor :: ToColor clr => clr -> Mod ctx
- pointer :: Mod c
- transition :: Ms -> TransitionProperty -> Mod c
- data TransitionProperty
- textAlign :: Align -> Mod c
- offset :: Sides Length -> Mod c
- position :: Position -> Mod c
- data Position
- zIndex :: Int -> Mod c
- display :: (Style Display a, ToClassName a) => a -> Mod c
- data Display = Block
- hover :: Mod c -> Mod c
- active :: Mod c -> Mod c
- even :: Mod c -> Mod c
- odd :: Mod c -> Mod c
- media :: Media -> Mod c -> Mod c
- parent :: Text -> Mod c -> Mod c
- applyPseudo :: Pseudo -> Mod c -> Mod c
- mapModClass :: (Class -> Class) -> Mod c -> Mod c
- addClass :: Class -> Mod c
- cls :: ClassName -> Class
- extClass :: ClassName -> Mod c
- prop :: ToStyleValue val => Name -> val -> Class -> Class
- (-.) :: ToClassName a => ClassName -> a -> ClassName
- class Style (style :: k) value where
- styleValue :: value -> StyleValue
Styles
minWidth :: Length -> Mod c Source #
Allow width to grow to contents but not shrink any smaller than value
minHeight :: Length -> Mod c Source #
Allow height to grow to contents but not shrink any smaller than value
pad :: Sides Length -> Mod c Source #
Space surrounding the children of the element
To create even spacing around and between all elements:
col (pad 10 . gap 10) $ do el_ "one" el_ "two" el_ "three"
shadow :: (Style Shadow a, ToClassName a) => a -> Mod c Source #
Add a drop shadow to an element
input (shadow Inner) "Inset Shadow" button (shadow ()) "Click Me"
Instances
Style Shadow Inner Source # | |
Defined in Web.View.Style styleValue :: Inner -> StyleValue Source # | |
Style Shadow None Source # | |
Defined in Web.View.Style styleValue :: None -> StyleValue Source # | |
Style Shadow () Source # | |
Defined in Web.View.Style styleValue :: () -> StyleValue Source # |
Instances
Show Inner Source # | |
ToClassName Inner Source # | |
Defined in Web.View.Style toClassName :: Inner -> ClassName Source # | |
Style Shadow Inner Source # | |
Defined in Web.View.Style styleValue :: Inner -> StyleValue Source # |
list :: (ToClassName a, Style ListType a) => a -> Mod c Source #
Set the list style of an item
ol id $ do li (list Decimal) "First" li (list Decimal) "Second" li (list Decimal) "Third"
Instances
Show ListType Source # | |
ToClassName ListType Source # | |
Defined in Web.View.Style toClassName :: ListType -> ClassName Source # | |
ToStyleValue ListType Source # | |
Defined in Web.View.Style toStyleValue :: ListType -> StyleValue Source # | |
Style ListType ListType Source # | |
Defined in Web.View.Style styleValue :: ListType -> StyleValue Source # | |
Style ListType None Source # | |
Defined in Web.View.Style styleValue :: None -> StyleValue Source # |
border :: Sides PxRem -> Mod c Source #
Set a border around the element
el (border 1) "all sides" el (border (X 1)) "only left and right"
Use a button-like cursor when hovering over the element
Button-like elements:
btn = pointer . bg Primary . hover (bg PrimaryLight) options = row id $ do el btn "Login" el btn "Sign Up"
transition :: Ms -> TransitionProperty -> Mod c 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.View.Style showsPrec :: Int -> TransitionProperty -> ShowS # show :: TransitionProperty -> String # showList :: [TransitionProperty] -> ShowS # |
Instances
Show Position Source # | |
ToClassName Position Source # | |
Defined in Web.View.Style toClassName :: Position -> ClassName Source # | |
ToStyleValue Position Source # | |
Defined in Web.View.Style toStyleValue :: Position -> StyleValue Source # |
display :: (Style Display a, ToClassName a) => a -> Mod c Source #
Set container display
el (display None) HIDDEN
Instances
Show Display Source # | |
ToClassName Display Source # | |
Defined in Web.View.Style toClassName :: Display -> ClassName Source # | |
ToStyleValue Display Source # | |
Defined in Web.View.Style toStyleValue :: Display -> StyleValue Source # | |
Style Display Display Source # | |
Defined in Web.View.Style styleValue :: Display -> StyleValue Source # | |
Style Display None Source # | |
Defined in Web.View.Style styleValue :: None -> StyleValue Source # |
Selector Modifiers
hover :: Mod c -> Mod c Source #
Apply when hovering over an element
el (bg Primary . hover (bg PrimaryLight)) "Hover"
media :: Media -> Mod c -> Mod c Source #
Apply when the Media matches the current window. This allows for responsive designs
el (width 100 . media (MinWidth 800) (width 400)) "Big if window > 800"
parent :: Text -> Mod c -> Mod c Source #
Apply when the element is somewhere inside an anscestor.
For example, the HTMX library applies an "htmx-request" class to the body when a request is pending. We can use this to create a loading indicator
el (pad 10) $ do el (parent "htmx-request" flexRow . hide) "Loading..." el (parent "htmx-request" hide . flexRow) "Normal Content"
Creating New Styles
addClass :: Class -> Mod c Source #
Add a single class
width :: PxRem -> Mod width n = addClass $ cls ("w" -. n) & prop "width" n & prop @Int "flex-shrink" 0
extClass :: ClassName -> Mod c Source #
Construct a mod from a ClassName with no CSS properties. Convenience for situations where external CSS classes need to be referenced.
el (extClass "btn" . extClass "btn-primary") "Click me!"
class Style (style :: k) value where Source #
Nothing
styleValue :: value -> StyleValue Source #
default styleValue :: ToStyleValue value => value -> StyleValue Source #
Instances
Style Display Display Source # | |
Defined in Web.View.Style styleValue :: Display -> StyleValue Source # | |
Style Display None Source # | |
Defined in Web.View.Style styleValue :: None -> StyleValue Source # | |
Style ListType ListType Source # | |
Defined in Web.View.Style styleValue :: ListType -> StyleValue Source # | |
Style ListType None Source # | |
Defined in Web.View.Style styleValue :: None -> StyleValue Source # | |
Style Shadow Inner Source # | |
Defined in Web.View.Style styleValue :: Inner -> StyleValue Source # | |
Style Shadow None Source # | |
Defined in Web.View.Style styleValue :: None -> StyleValue Source # | |
Style Shadow () Source # | |
Defined in Web.View.Style styleValue :: () -> StyleValue Source # |