{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Ditto.Generalized where
import Ditto.Backend
import Ditto.Core
import Ditto.Result
import qualified Ditto.Generalized.Internal as G
input :: (Monad m, FormError err input) => (input -> Either err a) -> (FormId -> a -> view) -> a -> Form m input err view a
input = G.input getFormId
inputMaybe
  :: (Monad m, FormError err input)
  => (input -> Either err a)
  -> (FormId -> Maybe a -> view)
  -> Maybe a
  -> Form m input err view (Maybe a)
inputMaybe = G.inputMaybe getFormId
inputMaybeReq
  :: (Monad m, FormError err input)
  => (input -> Either err a)
  -> (FormId -> Maybe a -> view)
  -> Maybe a
  -> Form m input err view a
inputMaybeReq = G.inputMaybeReq getFormId
inputNoData
  :: (Monad m)
  => (FormId -> view)
  -> Form m input err view ()
inputNoData = G.inputNoData getFormId
inputFile
  :: forall m input err view. (Monad m, FormInput input, FormError err input)
  => (FormId -> view)
  -> Form m input err view (FileType input)
inputFile = G.inputFile getFormId
inputMulti
  :: forall m input err view a lbl. (FormError err input, FormInput input, Monad m)
  => [(a, lbl)] 
  -> (FormId -> [(FormId, Int, lbl, Bool)] -> view) 
  -> (a -> Bool) 
  -> Form m input err view [a]
inputMulti = G.inputMulti getFormId
inputChoice
  :: forall a m err input lbl view. (FormError err input, FormInput input, Monad m)
  => (a -> Bool) 
  -> [(a, lbl)] 
  -> (FormId -> [(FormId, Int, lbl, Bool)] -> view) 
  -> Form m input err view a
inputChoice = G.inputChoice getFormId
inputChoiceForms
  :: forall a m err input lbl view. (Monad m, FormError err input, FormInput input)
  => a
  -> [(Form m input err view a, lbl)] 
  -> (FormId -> [(FormId, Int, FormId, view, lbl, Bool)] -> view) 
  -> Form m input err view a
inputChoiceForms = G.inputChoiceForms getFormId
label
  :: Monad m
  => (FormId -> view)
  -> Form m input err view ()
label = G.label getFormId
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