{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, ScopedTypeVariables, TypeFamilies, UndecidableInstances, ViewPatterns #-}
{- |
This module provides functions creating Reform using blaze-html markup.

This module assumes that you wish for text based controls such as 'inputText' and 'textarea' to using 'String' values. If you prefer 'Data.Text.Text' see "Text.Reform.Blaze.Text".

-}
module Text.Reform.Blaze.String
    ( -- * \<input\> element
      inputText
    , inputPassword
    , inputSubmit
    , inputReset
    , inputHidden
    , inputButton
    , C.inputCheckbox
    , C.inputCheckboxes
    , C.inputRadio
    , C.inputFile
      -- * \<textarea\> element
    , textarea
      -- * \<button\> element
    , buttonSubmit
    , C.buttonReset
    , C.button
      -- * \<select\> element
    , C.select
    , C.selectMultiple
      -- * \<label\> element
    , C.label
      -- * errors
    , C.errorList
    , C.childErrorList
      -- * layout functions
    , C.br
    , C.fieldset
    , C.ol
    , C.ul
    , C.li
    , C.form
    ) where

import Text.Blaze.Html (Html, ToMarkup)
import Text.Reform
import qualified Text.Reform.Blaze.Common as C

-- | Create an @\<input type=\"text\"\>@ element
inputText :: (Monad m, FormInput input, FormError error, ErrorInputType error ~ input) =>
               String -- ^ initial value
            -> Form m input error Html () String
inputText :: String -> Form m input error Html () String
inputText String
initialValue = (input -> Either error String)
-> String -> Form m input error Html () String
forall (m :: * -> *) error text input.
(Monad m, FormError error, ToValue text) =>
(input -> Either error text)
-> text -> Form m input error Html () text
C.inputText input -> Either error String
forall input error.
(FormInput input, FormError error, ErrorInputType error ~ input) =>
input -> Either error String
getInputString String
initialValue

-- | Create an @\<input type=\"password\"\>@ element
inputPassword :: (Monad m, FormInput input, FormError error, ErrorInputType error ~ input) =>
                 Form m input error Html () String
inputPassword :: Form m input error Html () String
inputPassword = (input -> Either error String)
-> String -> Form m input error Html () String
forall (m :: * -> *) error text input.
(Monad m, FormError error, ToValue text) =>
(input -> Either error text)
-> text -> Form m input error Html () text
C.inputPassword input -> Either error String
forall input error.
(FormInput input, FormError error, ErrorInputType error ~ input) =>
input -> Either error String
getInputString String
""

-- | Create an @\<input type=\"submit\"\>@ element
--
-- returns:
--
--   [@Just@ /value/] if this button was used to submit the form.
--
--   [@Nothing@]    if this button was not used to submit the form.
inputSubmit :: (Monad m, FormInput input, FormError error, ErrorInputType error ~ input) =>
               String -- ^ @value@ attribute. Used for button label, and value if button is submitted.
            -> Form m input error Html () (Maybe String)
inputSubmit :: String -> Form m input error Html () (Maybe String)
inputSubmit String
initialValue = (input -> Either error String)
-> String -> Form m input error Html () (Maybe String)
forall (m :: * -> *) error text input.
(Monad m, FormError error, ToValue text) =>
(input -> Either error text)
-> text -> Form m input error Html () (Maybe text)
C.inputSubmit input -> Either error String
forall input error.
(FormInput input, FormError error, ErrorInputType error ~ input) =>
input -> Either error String
getInputString String
initialValue

-- | Create an @\<input type=\"reset\"\>@ element
--
-- This element does not add any data to the form data set.
inputReset :: (Monad m, FormInput input, FormError error, ErrorInputType error ~ input) =>
              String -- ^ value attribute. Used only to label the button.
           -> Form m input error Html () ()
inputReset :: String -> Form m input error Html () ()
inputReset = String -> Form m input error Html () ()
forall (m :: * -> *) error text input.
(Monad m, FormError error, ToValue text) =>
text -> Form m input error Html () ()
C.inputReset

-- | Create an @\<input type=\"hidden\"\>@ element
inputHidden :: (Monad m, FormInput input, FormError error, ErrorInputType error ~ input) =>
               String -- ^ value to store in the hidden element
            -> Form m input error Html () String
inputHidden :: String -> Form m input error Html () String
inputHidden String
initialValue = (input -> Either error String)
-> String -> Form m input error Html () String
forall (m :: * -> *) error text input.
(Monad m, FormError error, ToValue text) =>
(input -> Either error text)
-> text -> Form m input error Html () text
C.inputHidden input -> Either error String
forall input error.
(FormInput input, FormError error, ErrorInputType error ~ input) =>
input -> Either error String
getInputString String
initialValue

-- | Create an @\<input type=\"button\"\>@ element
--
-- The element is a push button with a text label. The button does nothing by default, but actions can be added using javascript. This element does not add any data to the form data set.
--
-- see also: 'C.button'
inputButton :: (Monad m, FormInput input, FormError error, ErrorInputType error ~ input) =>
               String -- ^ value attribute. Used to label the button.
            -> Form m input error Html () ()
inputButton :: String -> Form m input error Html () ()
inputButton String
label = String -> Form m input error Html () ()
forall (m :: * -> *) error text input.
(Monad m, FormError error, ToValue text) =>
text -> Form m input error Html () ()
C.inputButton String
label

-- | Create a \<textarea\>\<\/textarea\> element
textarea :: (Monad m, FormInput input, FormError error, ErrorInputType error ~ input) =>
            Int    -- ^ cols
         -> Int    -- ^ rows
         -> String -- ^ initial contents
         -> Form m input error Html () String
textarea :: Int -> Int -> String -> Form m input error Html () String
textarea Int
rows Int
cols String
initialValue = (input -> Either error String)
-> Int -> Int -> String -> Form m input error Html () String
forall (m :: * -> *) error text input.
(Monad m, FormError error, ToMarkup text) =>
(input -> Either error text)
-> Int -> Int -> text -> Form m input error Html () text
C.textarea input -> Either error String
forall input error.
(FormInput input, FormError error, ErrorInputType error ~ input) =>
input -> Either error String
getInputString Int
rows Int
cols String
initialValue

-- | create a  @\<button type=\"submit\"\>\<\/button\>@ element
buttonSubmit :: ( Monad m, FormError error, FormInput input, ErrorInputType error ~ input, ToMarkup children) =>
                String -- ^ value attribute. Returned if this button submits the form.
             -> children -- ^ children to embed in the \<button\>
             -> Form m input error Html () (Maybe String)
buttonSubmit :: String -> children -> Form m input error Html () (Maybe String)
buttonSubmit = (input -> Either error String)
-> String -> children -> Form m input error Html () (Maybe String)
forall (m :: * -> *) error text children input.
(Monad m, FormError error, ToValue text, ToMarkup children) =>
(input -> Either error text)
-> text -> children -> Form m input error Html () (Maybe text)
C.buttonSubmit input -> Either error String
forall input error.
(FormInput input, FormError error, ErrorInputType error ~ input) =>
input -> Either error String
getInputString