web-view-0.4.0: Type-safe HTML and CSS with intuitive layouts and composable styles.
Safe HaskellSafe-Inferred
LanguageGHC2021

Web.View.Types

Synopsis

Documentation

data Content Source #

Constructors

Node Element 
Text Text 
Raw Text

Raw embedded HTML or SVG. See raw

data Element Source #

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 

data Attributes Source #

Constructors

Attributes 

Fields

Instances

Instances details
Monoid Attributes Source # 
Instance details

Defined in Web.View.Types

Semigroup Attributes Source # 
Instance details

Defined in Web.View.Types

type Name = Text Source #

Attribute Modifiers

type Mod = Attributes -> Attributes Source #

Element functions expect a Mod function as their first argument that adds attributes and classes.

userEmail :: User -> View c ()
userEmail user = input (fontSize 16 . active) (text user.email)
  where
    active = isActive user then bold else id

Atomic CSS

type CSS = Map Selector Class Source #

All the atomic classes used in a View

data Class Source #

Atomic classes include a selector and the corresponding styles

Constructors

Class 

type Styles = Map Name StyleValue Source #

The styles to apply for a given atomic Class

data Selector Source #

The selector to use for the given atomic Class

Instances

Instances details
IsString Selector Source # 
Instance details

Defined in Web.View.Types

Eq Selector Source # 
Instance details

Defined in Web.View.Types

Ord Selector Source # 
Instance details

Defined in Web.View.Types

selector :: ClassName -> Selector Source #

Create a Selector given only a ClassName

newtype ClassName Source #

A class name

Constructors

ClassName 

Fields

Instances

Instances details
IsString ClassName Source # 
Instance details

Defined in Web.View.Types

Eq ClassName Source # 
Instance details

Defined in Web.View.Types

Ord ClassName Source # 
Instance details

Defined in Web.View.Types

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

default toClassName :: Show a => a -> Text Source #

Instances

Instances details
ToClassName Text Source # 
Instance details

Defined in Web.View.Types

ToClassName Align Source # 
Instance details

Defined in Web.View.Types

ToClassName Length Source # 
Instance details

Defined in Web.View.Types

ToClassName Ms Source # 
Instance details

Defined in Web.View.Types

Methods

toClassName :: Ms -> Text Source #

ToClassName PxRem Source # 
Instance details

Defined in Web.View.Types

ToClassName Float Source # 
Instance details

Defined in Web.View.Types

ToClassName Int Source # 
Instance details

Defined in Web.View.Types

Methods

toClassName :: Int -> Text Source #

data Pseudo Source #

Psuedos allow for specifying styles that only apply in certain conditions. See hover etc

el (color Primary . hover (color White)) "hello"

Constructors

Hover 
Active 
Even 
Odd 

Instances

Instances details
Show Pseudo Source # 
Instance details

Defined in Web.View.Types

Eq Pseudo Source # 
Instance details

Defined in Web.View.Types

Methods

(==) :: Pseudo -> Pseudo -> Bool #

(/=) :: Pseudo -> Pseudo -> Bool #

Ord Pseudo Source # 
Instance details

Defined in Web.View.Types

newtype StyleValue Source #

The value of a css style property

Constructors

StyleValue String 

Instances

Instances details
IsString StyleValue Source # 
Instance details

Defined in Web.View.Types

Show StyleValue Source # 
Instance details

Defined in Web.View.Types

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

Instances details
ToStyleValue Text Source # 
Instance details

Defined in Web.View.Types

ToStyleValue Align Source # 
Instance details

Defined in Web.View.Types

ToStyleValue HexColor Source # 
Instance details

Defined in Web.View.Types

ToStyleValue Length Source # 
Instance details

Defined in Web.View.Types

ToStyleValue Ms Source # 
Instance details

Defined in Web.View.Types

ToStyleValue PxRem Source # 
Instance details

Defined in Web.View.Types

ToStyleValue String Source # 
Instance details

Defined in Web.View.Types

ToStyleValue Float Source # 
Instance details

Defined in Web.View.Types

ToStyleValue Int Source # 
Instance details

Defined in Web.View.Types

data Length Source #

Constructors

PxRem PxRem

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

Pct Float 

Instances

Instances details
Num Length Source # 
Instance details

Defined in Web.View.Types

Show Length Source # 
Instance details

Defined in Web.View.Types

ToClassName Length Source # 
Instance details

Defined in Web.View.Types

ToStyleValue Length Source # 
Instance details

Defined in Web.View.Types

newtype PxRem Source #

Constructors

PxRem' Int 

Instances

Instances details
Enum PxRem Source # 
Instance details

Defined in Web.View.Types

Num PxRem Source # 
Instance details

Defined in Web.View.Types

Integral PxRem Source # 
Instance details

Defined in Web.View.Types

Real PxRem Source # 
Instance details

Defined in Web.View.Types

Methods

toRational :: PxRem -> Rational #

Show PxRem Source # 
Instance details

Defined in Web.View.Types

Methods

showsPrec :: Int -> PxRem -> ShowS #

show :: PxRem -> String #

showList :: [PxRem] -> ShowS #

Eq PxRem Source # 
Instance details

Defined in Web.View.Types

Methods

(==) :: PxRem -> PxRem -> Bool #

(/=) :: PxRem -> PxRem -> Bool #

Ord PxRem Source # 
Instance details

Defined in Web.View.Types

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 #

ToClassName PxRem Source # 
Instance details

Defined in Web.View.Types

ToStyleValue PxRem Source # 
Instance details

Defined in Web.View.Types

newtype Ms Source #

Milliseconds, used for transitions

Constructors

Ms Int 

Instances

Instances details
Num Ms Source # 
Instance details

Defined in Web.View.Types

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.View.Types

Methods

showsPrec :: Int -> Ms -> ShowS #

show :: Ms -> String #

showList :: [Ms] -> ShowS #

ToClassName Ms Source # 
Instance details

Defined in Web.View.Types

Methods

toClassName :: Ms -> Text Source #

ToStyleValue Ms Source # 
Instance details

Defined in Web.View.Types

data Media Source #

Media allows for responsive designs that change based on characteristics of the window. See Layout Example

Constructors

MinWidth Int 
MaxWidth Int 

Instances

Instances details
Eq Media Source # 
Instance details

Defined in Web.View.Types

Methods

(==) :: Media -> Media -> Bool #

(/=) :: Media -> Media -> Bool #

Ord Media Source # 
Instance details

Defined in Web.View.Types

Methods

compare :: Media -> Media -> Ordering #

(<) :: Media -> Media -> Bool #

(<=) :: Media -> Media -> Bool #

(>) :: Media -> Media -> Bool #

(>=) :: Media -> Media -> Bool #

max :: Media -> Media -> Media #

min :: Media -> Media -> Media #

data Sides a Source #

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)

Constructors

All a 
TRBL a a a a 
X a 
Y a 
XY a a 

Instances

Instances details
Num a => Num (Sides a) Source # 
Instance details

Defined in Web.View.Types

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 #

newtype FlatAttributes Source #

Element's attributes do not include class, which is separated. FlatAttributes generate the class attribute and include it

Constructors

FlatAttributes 

Instances

Instances details
Generic FlatAttributes Source # 
Instance details

Defined in Web.View.Types

Associated Types

type Rep FlatAttributes :: Type -> Type #

type Rep FlatAttributes Source # 
Instance details

Defined in Web.View.Types

type Rep FlatAttributes = D1 ('MetaData "FlatAttributes" "Web.View.Types" "web-view-0.4.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

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.View.Types

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
IsString HexColor Source # 
Instance details

Defined in Web.View.Types

ToColor HexColor Source # 
Instance details

Defined in Web.View.Types

ToStyleValue HexColor Source # 
Instance details

Defined in Web.View.Types

data Align Source #

Constructors

Center 

Instances

Instances details
Show Align Source # 
Instance details

Defined in Web.View.Types

Methods

showsPrec :: Int -> Align -> ShowS #

show :: Align -> String #

showList :: [Align] -> ShowS #

ToClassName Align Source # 
Instance details

Defined in Web.View.Types

ToStyleValue Align Source # 
Instance details

Defined in Web.View.Types