{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DoAndIfThenElse #-}
module Ditto.Generalized.Named where
import Ditto.Backend
import Ditto.Core
import Ditto.Result
import qualified Ditto.Generalized.Internal as G
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)
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)
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)
inputNoData
  :: (Monad m)
  => String
  -> (FormId -> view)
  -> Form m input err view ()
inputNoData name = G.inputNoData (getNamedFormId name)
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)
inputMulti
  :: forall m input err view a lbl. (FormError err input, FormInput input, Monad m)
  => String
  -> [(a, lbl)] 
  -> (FormId -> [(FormId, Int, lbl, Bool)] -> view) 
  -> (a -> Bool) 
  -> Form m input err view [a]
inputMulti name = G.inputMulti (getNamedFormId name)
inputChoice
  :: forall a m err input lbl view. (FormError err input, FormInput input, Monad m)
  => String
  -> (a -> Bool) 
  -> [(a, lbl)] 
  -> (FormId -> [(FormId, Int, lbl, Bool)] -> view) 
  -> Form m input err view a
inputChoice name = G.inputChoice (getNamedFormId name)
inputChoiceForms
  :: forall a m err input lbl view. (Monad m, FormError err input, FormInput input)
  => String
  -> a
  -> [(Form m input err view a, lbl)] 
  -> (FormId -> [(FormId, Int, FormId, view, lbl, Bool)] -> view) 
  -> Form m input err view a
inputChoiceForms name = G.inputChoiceForms (getNamedFormId name)
label
  :: Monad m
  => String
  -> (FormId -> view)
  -> Form m input err view ()
label name = G.label (getNamedFormId name)
errors
  :: Monad m
  => ([err] -> view) 
  -> Form m input err view ()
errors = G.errors
childErrors
  :: Monad m
  => ([err] -> view)
  -> Form m input err view ()
childErrors = G.childErrors
withErrors
  :: Monad m
  => (view -> [err] -> view)
  -> Form m input err view a
  -> Form m input err view a
withErrors = G.withErrors