{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE DoAndIfThenElse #-} -- This module provides helper functions for HTML input elements. These helper functions are not specific to any particular web framework or html library. module Ditto.Generalized.Named where import Ditto.Backend import Ditto.Core import Ditto.Result import qualified Ditto.Generalized.Internal as G -- | used for constructing elements like @\@, which pure a single input value. input :: (Monad m, FormError err input) => String -> (input -> Either err a) -> (FormId -> a -> view) -> a -> Form m input err view a input name = G.input (getNamedFormId name) -- | used to construct elements with optional initial values, which are still required inputMaybeReq :: (Monad m, FormError err input) => String -> (input -> Either err a) -> (FormId -> Maybe a -> view) -> Maybe a -> Form m input err view a inputMaybeReq name = G.inputMaybeReq (getNamedFormId name) -- | used for elements like @\@ which are not always present in the form submission data. inputMaybe :: (Monad m, FormError err input) => String -> (input -> Either err a) -> (FormId -> Maybe a -> view) -> Maybe a -> Form m input err view (Maybe a) inputMaybe name = G.inputMaybe (getNamedFormId name) -- | used for elements like @\@ which take a value, but are never present in the form data set. inputNoData :: (Monad m) => String -> (FormId -> view) -> Form m input err view () inputNoData name = G.inputNoData (getNamedFormId name) -- | used for @\@ inputFile :: forall m input err view. (Monad m, FormInput input, FormError err input) => String -> (FormId -> view) -> Form m input err view (FileType input) inputFile name = G.inputFile (getNamedFormId name) -- | used for groups of checkboxes, @\