ditto-lucid-0.4: Add support for using lucid with Ditto

Safe HaskellNone
LanguageHaskell98

Ditto.Lucid.Unnamed

Synopsis

Documentation

foldTraverse_ :: (Foldable t, Applicative f, Monoid (f b)) => (a -> t (f b)) -> t a -> f () Source #

inputText :: (Environment m input, FormError input err, PathPiece text, Applicative f) => (input -> Either err text) -> text -> Form m input err (HtmlT f ()) text Source #

inputMaybeText :: (Environment m input, FormError input err, PathPiece text, Applicative f) => (input -> Either err text) -> Maybe text -> Form m input err (HtmlT f ()) (Maybe text) Source #

inputPassword :: (Environment m input, FormError input err, PathPiece text, Applicative f) => (input -> Either err text) -> text -> Form m input err (HtmlT f ()) text Source #

inputSubmit :: (Environment m input, FormError input err, PathPiece text, Applicative f) => (input -> Either err text) -> text -> Form m input err (HtmlT f ()) (Maybe text) Source #

inputReset :: (Environment m input, FormError input err, PathPiece text, Applicative f) => text -> Form m input err (HtmlT f ()) () Source #

inputHidden :: (Environment m input, FormError input err, PathPiece text, Applicative f) => (input -> Either err text) -> text -> Form m input err (HtmlT f ()) text Source #

inputButton :: (Environment m input, FormError input err, PathPiece text, Applicative f) => text -> Form m input err (HtmlT f ()) () Source #

textarea Source #

Arguments

:: (Environment m input, FormError input err, ToHtml text, Monad f) 
=> (input -> Either err text) 
-> Int

cols

-> Int

rows

-> text

initial text

-> Form m input err (HtmlT f ()) text 

inputFile :: (Environment m input, FormError input err, FormInput input, Applicative f, ft ~ FileType input, Monoid ft) => Form m input err (HtmlT f ()) (FileType input) Source #

Create an <input type="file"> element

This control may succeed even if the user does not actually select a file to upload. In that case the uploaded name will likely be "" and the file contents will be empty as well.

buttonSubmit :: (Environment m input, FormError input err, PathPiece text, ToHtml children, Monad f) => (input -> Either err text) -> text -> children -> Form m input err (HtmlT f ()) (Maybe text) Source #

Create a <button type="submit"> element

buttonReset :: (Environment m input, FormError input err, ToHtml children, Monad f) => children -> Form m input err (HtmlT f ()) () Source #

create a <button type="reset"></button> element

This element does not add any data to the form data set.

button :: (Environment m input, FormError input err, ToHtml children, Monad f) => children -> Form m input err (HtmlT f ()) () Source #

create a <button type="button"></button> element

This element does not add any data to the form data set.

label :: (Environment m input, Monad f) => HtmlT f () -> Form m input err (HtmlT f ()) () Source #

create a <label> element.

Use this with or ++ to ensure that the for attribute references the correct id.

label "some input field: " ++> inputText ""

arbitraryHtml :: Environment m input => view -> Form m input err view () Source #

inputInt :: (Environment m input, FormError input err, Applicative f) => (input -> Either err Int) -> Int -> Form m input err (HtmlT f ()) Int Source #

inputDouble :: (Environment m input, FormError input err, Applicative f) => (input -> Either err Double) -> Double -> Form m input err (HtmlT f ()) Double Source #

inputCheckbox Source #

Arguments

:: (Environment m input, FormError input err, Applicative f) 
=> Bool

initially checked

-> Form m input err (HtmlT f ()) Bool 

Create a single <input type="checkbox"> element

returns a Bool indicating if it was checked or not.

see also inputCheckboxes

inputCheckboxes Source #

Arguments

:: (Functor m, Environment m input, FormError input err, FormInput input, Monad f, PathPiece a, Eq a) 
=> [(a, Html ())]

value, label, initially checked

-> (input -> Either err [a]) 
-> (a -> Bool)

function which indicates if a value should be checked initially

-> Form m input err (HtmlT f ()) [a] 

Create a group of <input type="checkbox"> elements

inputRadio Source #

Arguments

:: (Functor m, Environment m input, FormError input err, FormInput input, Monad f, PathPiece a, Eq a) 
=> NonEmpty (a, Html ())

value, label, initially checked

-> (input -> Either err a) 
-> (a -> Bool)

isDefault

-> Form m input err (HtmlT f ()) a 

Create a group of <input type="radio"> elements

select Source #

Arguments

:: (Functor m, Environment m input, FormError input err, FormInput input, Monad f, PathPiece a, Eq a) 
=> NonEmpty (a, Html ())

value, label

-> (input -> Either err a) 
-> (a -> Bool)

isDefault, must match *exactly one* element in the list of choices

-> Form m input err (HtmlT f ()) a 

create <select></select> element plus its <option></option> children.

see also: selectMultiple

selectMultiple Source #

Arguments

:: (Functor m, Environment m input, FormError input err, FormInput input, Monad f, PathPiece a, Eq a) 
=> [(a, Html ())]

value, label, initially checked

-> (input -> Either err [a]) 
-> (a -> Bool)

isSelected initially

-> Form m input err (HtmlT f ()) [a] 

create <select multiple="multiple"></select> element plus its <option></option> children.

This creates a <select> element which allows more than one item to be selected.