{-# LANGUAGE ScopedTypeVariables , TypeFamilies #-} -- | This module provides helper functions for HTML input elements. These helper functions are not specific to any particular web framework or html library. -- -- Additionally, the inputs generated with the functions from this module will have their names/ids automatically enumerated. -- -- For named formlets, see @Ditto.Generalized.Named@ module Ditto.Generalized.Unnamed ( G.Choice(..) , input , inputMaybe , inputNoData , inputFile , inputMulti , inputChoice , inputList , label , errors , childErrors , withErrors , G.withChildErrors ) where import Data.List.NonEmpty (NonEmpty(..)) import Ditto.Backend import Ditto.Core import Ditto.Types import qualified Ditto.Generalized.Internal as G -- | used for constructing elements like @\@, which pure a single input value. input :: (Environment m input, FormError input err) => (input -> Either err a) -> (FormId -> a -> view) -> a -> Form m input err view a input = G.input getFormId -- | used for elements like @\@ which are not always present in the form submission data. inputMaybe :: (Environment m input, FormError input err) => (input -> Either err a) -> (FormId -> Maybe a -> view) -> Maybe a -> Form m input err view (Maybe a) inputMaybe = G.inputMaybe getFormId -- | used for elements like @\@ which take a value, but are never present in the form data set. inputNoData :: (Environment m input) => (FormId -> view) -> Form m input err view () inputNoData = G.inputNoData getFormId -- | used for @\@ inputFile :: forall m input err view ft. (Environment m input, FormInput input, FormError input err, ft ~ FileType input, Monoid ft) => (FormId -> view) -> Form m input err view (FileType input) inputFile = G.inputFile getFormId -- | used for groups of checkboxes, @\