| Safe Haskell | None | 
|---|---|
| Language | GHC2021 | 
Web.View.Types
Synopsis
- data Content
- data Element = Element {- inline :: Bool
- name :: Name
- attributes :: Attributes ()
- children :: [Content]
 
- element :: forall {k} (c :: k). Name -> Attributes c -> [Content] -> Element
- stripContext :: forall {k1} {k2} (a :: k1) (b :: k2). Attributes a -> Attributes b
- data Attributes (c :: k) = Attributes {}
- type Attribute = (Name, AttValue)
- type Name = Text
- type AttValue = Text
- type Mod context = Attributes context -> Attributes context
- type CSS = Map Selector Class
- data Class = Class {- selector :: Selector
- properties :: Styles
 
- type Styles = Map Name StyleValue
- type Ancestor = Text
- data ChildCombinator
- data Selector = Selector {}
- selector :: ClassName -> Selector
- newtype ClassName = ClassName {}
- className :: Text -> ClassName
- class ToClassName a where- toClassName :: a -> ClassName
 
- data Pseudo
- newtype StyleValue = StyleValue String
- class ToStyleValue a where- toStyleValue :: a -> StyleValue
 
- class ToProp a where
- data Length
- newtype PxRem = PxRem' Int
- newtype Ms = Ms Int
- data Media
- data Sides a
- newtype FlatAttributes = FlatAttributes {}
- class ToColor a where- colorValue :: a -> HexColor
- colorName :: a -> Text
 
- newtype HexColor = HexColor Text
- data Align
- data None = None
- class Style (cls :: k) value where- styleValue :: value -> StyleValue
 
- class ToClass (cls :: k) value where
Documentation
A single HTML tag. Note that the class attribute is stored separately from the rest of the attributes to make adding styles easier
Constructors
| Element | |
| Fields 
 | |
element :: forall {k} (c :: k). Name -> Attributes c -> [Content] -> Element Source #
Construct an Element
stripContext :: forall {k1} {k2} (a :: k1) (b :: k2). Attributes a -> Attributes b Source #
Internal. Convert an Attributes to any context
data Attributes (c :: k) Source #
The Attributes for an Element. Classes are merged and managed separately from the other attributes.
Instances
| Monoid (Attributes c) Source # | |
| Defined in Web.View.Types Methods mempty :: Attributes c # mappend :: Attributes c -> Attributes c -> Attributes c # mconcat :: [Attributes c] -> Attributes c # | |
| Semigroup (Attributes c) Source # | |
| Defined in Web.View.Types Methods (<>) :: Attributes c -> Attributes c -> Attributes c # sconcat :: NonEmpty (Attributes c) -> Attributes c # stimes :: Integral b => b -> Attributes c -> Attributes c # | |
| Show (Attributes c) Source # | |
| Defined in Web.View.Types Methods showsPrec :: Int -> Attributes c -> ShowS # show :: Attributes c -> String # showList :: [Attributes c] -> ShowS # | |
| Eq (Attributes c) Source # | |
| Defined in Web.View.Types | |
Attribute Modifiers
type Mod context = Attributes context -> Attributes context Source #
Element functions expect a modifier function as their first argument. These can add attributes and classes. Combine multiple Mods with (.)
userEmail :: User -> View c ()
userEmail user = input (fontSize 16 . active) (text user.email)
  where
    active = isActive user then bold else idIf you don't want to specify any attributes, you can use id
plainView :: View c () plainView = el id "No styles"
Atomic CSS
Atomic classes include a selector and the corresponding styles
Constructors
| Class | |
| Fields 
 | |
A parent selector limits the selector to only apply when a descendent of the parent in question
data ChildCombinator Source #
A child selector limits
Constructors
| AllChildren | |
| ChildWithName Text | 
Instances
| IsString ChildCombinator Source # | |
| Defined in Web.View.Types Methods fromString :: String -> ChildCombinator # | |
| Show ChildCombinator Source # | |
| Defined in Web.View.Types Methods showsPrec :: Int -> ChildCombinator -> ShowS # show :: ChildCombinator -> String # showList :: [ChildCombinator] -> ShowS # | |
| Eq ChildCombinator Source # | |
| Defined in Web.View.Types Methods (==) :: ChildCombinator -> ChildCombinator -> Bool # (/=) :: ChildCombinator -> ChildCombinator -> Bool # | |
| Ord ChildCombinator Source # | |
| Defined in Web.View.Types Methods compare :: ChildCombinator -> ChildCombinator -> Ordering # (<) :: ChildCombinator -> ChildCombinator -> Bool # (<=) :: ChildCombinator -> ChildCombinator -> Bool # (>) :: ChildCombinator -> ChildCombinator -> Bool # (>=) :: ChildCombinator -> ChildCombinator -> Bool # max :: ChildCombinator -> ChildCombinator -> ChildCombinator # min :: ChildCombinator -> ChildCombinator -> ChildCombinator # | |
The selector to use for the given atomic Class
Constructors
| Selector | |
A class name
Instances
| IsString ClassName Source # | |
| Defined in Web.View.Types Methods fromString :: String -> ClassName # | |
| Monoid ClassName Source # | |
| Semigroup ClassName Source # | |
| Show ClassName Source # | |
| Eq ClassName Source # | |
| Ord ClassName Source # | |
class ToClassName a where Source #
Convert a type into a className segment to generate unique compound style names based on the value
Minimal complete definition
Nothing
Methods
toClassName :: a -> ClassName Source #
default toClassName :: Show a => a -> ClassName Source #
Instances
Psuedos allow for specifying styles that only apply in certain conditions. See hover etc
el (color Primary . hover (color White)) "hello"
newtype StyleValue Source #
The value of a css style property
Constructors
| StyleValue String | 
Instances
| IsString StyleValue Source # | |
| Defined in Web.View.Types Methods fromString :: String -> StyleValue # | |
| Monoid StyleValue Source # | |
| Defined in Web.View.Types Methods mempty :: StyleValue # mappend :: StyleValue -> StyleValue -> StyleValue # mconcat :: [StyleValue] -> StyleValue # | |
| Semigroup StyleValue Source # | |
| Defined in Web.View.Types Methods (<>) :: StyleValue -> StyleValue -> StyleValue # sconcat :: NonEmpty StyleValue -> StyleValue # stimes :: Integral b => b -> StyleValue -> StyleValue # | |
| Show StyleValue Source # | |
| Defined in Web.View.Types Methods showsPrec :: Int -> StyleValue -> ShowS # show :: StyleValue -> String # showList :: [StyleValue] -> ShowS # | |
| Eq StyleValue Source # | |
| Defined in Web.View.Types | |
| ToStyleValue StyleValue Source # | |
| Defined in Web.View.Types Methods toStyleValue :: StyleValue -> StyleValue Source # | |
class ToStyleValue a where Source #
Use a type as a css style property value
Minimal complete definition
Nothing
Methods
toStyleValue :: a -> StyleValue Source #
default toStyleValue :: Show a => a -> StyleValue Source #
Instances
Convert a type to a prop name
Minimal complete definition
Nothing
Instances
| Num Length Source # | |
| Show Length Source # | |
| ToClassName Length Source # | |
| Defined in Web.View.Types Methods toClassName :: Length -> ClassName Source # | |
| ToStyleValue Length Source # | |
| Defined in Web.View.Types Methods toStyleValue :: Length -> StyleValue 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
| Enum PxRem Source # | |
| Num PxRem Source # | |
| Integral PxRem Source # | |
| Real PxRem Source # | |
| Defined in Web.View.Types Methods toRational :: PxRem -> Rational # | |
| Show PxRem Source # | |
| Eq PxRem Source # | |
| Ord PxRem Source # | |
| ToClassName PxRem Source # | |
| Defined in Web.View.Types Methods toClassName :: PxRem -> ClassName Source # | |
| ToStyleValue PxRem Source # | |
| Defined in Web.View.Types Methods toStyleValue :: PxRem -> StyleValue Source # | |
Milliseconds, used for transitions
Instances
| Num Ms Source # | |
| Show Ms Source # | |
| ToClassName Ms Source # | |
| Defined in Web.View.Types Methods toClassName :: Ms -> ClassName Source # | |
| ToStyleValue Ms Source # | |
| Defined in Web.View.Types Methods toStyleValue :: Ms -> StyleValue Source # | |
Media allows for responsive designs that change based on characteristics of the window. See Layout Example
Options for styles that support specifying various sides. This has a "fake" Num instance to support literals
border 5 border (X 2) border (TRBL 0 5 0 0)
newtype FlatAttributes Source #
Element's attributes do not include class, which is separated. FlatAttributes generate the class attribute and include it
Constructors
| FlatAttributes | |
| Fields | |
Instances
| Generic FlatAttributes Source # | |||||
| Defined in Web.View.Types Associated Types 
 Methods from :: FlatAttributes -> Rep FlatAttributes x # to :: Rep FlatAttributes x -> FlatAttributes # | |||||
| type Rep FlatAttributes Source # | |||||
| Defined in Web.View.Types type Rep FlatAttributes = D1 ('MetaData "FlatAttributes" "Web.View.Types" "web-view-0.7.0-inplace" 'True) (C1 ('MetaCons "FlatAttributes" 'PrefixI 'True) (S1 ('MetaSel ('Just "attributes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Name AttValue)))) | |||||
Colors
class ToColor a where Source #
ToColor allows you to create a type containing your application's colors:
data AppColor = White | Primary | Dark instance ToColor AppColor where colorValue White = "#FFF" colorValue Dark = "#333" colorValue Primary = "#00F" hello :: View c () 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
| IsString HexColor Source # | |
| Defined in Web.View.Types Methods fromString :: String -> HexColor # | |
| Show HexColor Source # | |
| ToClassName HexColor Source # | |
| Defined in Web.View.Types Methods toClassName :: HexColor -> ClassName Source # | |
| ToColor HexColor Source # | |
| ToStyleValue HexColor Source # | |
| Defined in Web.View.Types Methods toStyleValue :: HexColor -> StyleValue Source # | |
Constructors
| AlignCenter | |
| AlignLeft | |
| AlignRight | |
| AlignJustify | 
Instances
| Show Align Source # | |
| ToClassName Align Source # | |
| Defined in Web.View.Types Methods toClassName :: Align -> ClassName Source # | |
| ToStyleValue Align Source # | |
| Defined in Web.View.Types Methods toStyleValue :: Align -> StyleValue Source # | |
Constructors
| None | 
Instances
| Show None Source # | |
| ToClassName None Source # | |
| Defined in Web.View.Types Methods toClassName :: None -> ClassName Source # | |
| ToStyleValue None Source # | |
| Defined in Web.View.Types Methods toStyleValue :: None -> StyleValue Source # | |
| Style Display None Source # | |
| Defined in Web.View.Style Methods styleValue :: None -> StyleValue Source # | |
| Style ListType None Source # | |
| Defined in Web.View.Style Methods styleValue :: None -> StyleValue Source # | |
| Style Shadow None Source # | |
| Defined in Web.View.Style Methods styleValue :: None -> StyleValue Source # | |
class Style (cls :: k) value where Source #
Minimal complete definition
Nothing
Methods
styleValue :: value -> StyleValue Source #
default styleValue :: ToStyleValue value => value -> StyleValue Source #
Instances
| Style Display Display Source # | |
| Defined in Web.View.Style Methods styleValue :: Display -> StyleValue Source # | |
| Style Display None Source # | |
| Defined in Web.View.Style Methods styleValue :: None -> StyleValue Source # | |
| Style ListType ListType Source # | |
| Defined in Web.View.Style Methods styleValue :: ListType -> StyleValue Source # | |
| Style ListType None Source # | |
| Defined in Web.View.Style Methods styleValue :: None -> StyleValue Source # | |
| Style Shadow Inner Source # | |
| Defined in Web.View.Style Methods styleValue :: Inner -> StyleValue Source # | |
| Style Shadow None Source # | |
| Defined in Web.View.Style Methods styleValue :: None -> StyleValue Source # | |
| Style Shadow () Source # | |
| Defined in Web.View.Style Methods styleValue :: () -> StyleValue Source # | |