type-of-html-1.5.2.0: High performance type driven html generation.

Safe HaskellNone
LanguageHaskell2010

Html.Attribute

Synopsis

Documentation

role_ :: a -> RoleA := a Source #

align_ :: a -> AlignA := a Source #

alt_ :: a -> AltA := a Source #

cite_ :: a -> CiteA := a Source #

class_ :: a -> ClassA := a Source #

code_ :: a -> CodeA := a Source #

color_ :: a -> ColorA := a Source #

cols_ :: Integral a => a -> ColsA := a Source #

data_ :: a -> DataA := a Source #

dir_ :: a -> DirA := a Source #

for_ :: a -> ForA := a Source #

form_ :: a -> FormA := a Source #

high_ :: Num a => a -> HighA := a Source #

href_ :: a -> HrefA := a Source #

icon_ :: a -> IconA := a Source #

id_ :: a -> IdA := a Source #

kind_ :: a -> KindA := a Source #

label_ :: a -> LabelA := a Source #

lang_ :: a -> LangA := a Source #

list_ :: a -> ListA := a Source #

low_ :: Num a => a -> LowA := a Source #

max_ :: Num a => a -> MaxA := a Source #

media_ :: a -> MediaA := a Source #

min_ :: Num a => a -> MinA := a Source #

name_ :: a -> NameA := a Source #

nonce_ :: a -> NonceA := a Source #

optimum_ :: Num a => a -> OptimumA := a Source #

ping_ :: a -> PingA := a Source #

rel_ :: a -> RelA := a Source #

rev_ :: a -> RevA := a Source #

rows_ :: Integral a => a -> RowsA := a Source #

scope_ :: a -> ScopeA := a Source #

shape_ :: a -> ShapeA := a Source #

size_ :: Integral a => a -> SizeA := a Source #

sizes_ :: a -> SizesA := a Source #

slot_ :: a -> SlotA := a Source #

span_ :: Integral a => a -> SpanA := a Source #

src_ :: a -> SrcA := a Source #

start_ :: Integral a => a -> StartA := a Source #

step_ :: Num a => a -> StepA := a Source #

style_ :: a -> StyleA := a Source #

title_ :: a -> TitleA := a Source #

type_ :: a -> TypeA := a Source #

value_ :: a -> ValueA := a Source #

width_ :: Integral a => a -> WidthA := a Source #

wrap_ :: a -> WrapA := a Source #

custom_ :: a -> CustomA b := a Source #

Escape hatch for defining non standard attributes. Note that it's your responsibility to choose valid attribute names, these are at the moment not checked. These custom attributes don't carry any performance penalty, they are fused at compiletime just as much as standard attributes.

  {-# LANGUAGE DataKinds #-}
  {-# LANGUAGE TypeOperators #-}
  import Html
  import qualified Html.Attribute as A

  dataName_ :: a -> 'CustomA "data-name" := a
  dataName_ = A.custom_
>>> div_A (dataName_ "foo") "bar"
<div data-name="foo">bar</div>

addAttributes :: (a <?> (b # b')) c => b' -> (a :@: b) c -> (a :@: (b # b')) c Source #