{-# LANGUAGE
ScopedTypeVariables
, TypeFamilies
#-}
module Ditto.Generalized.Named
( G.Choice(..)
, input
, inputMaybe
, inputNoData
, inputFile
, inputMulti
, inputChoice
, inputList
, label
, errors
, childErrors
, withErrors
, G.withChildErrors
, ireq
, iopt
) where
import Ditto.Backend
import Ditto.Core
import Ditto.Types
import Data.Text (Text)
import Data.List.NonEmpty (NonEmpty(..))
import qualified Ditto.Generalized.Internal as G
input :: (Environment m input, FormError input err)
=> Text
-> (input -> Either err a)
-> (FormId -> a -> view)
-> a
-> Form m input err view a
input name = G.input (getNamedFormId name)
inputMaybe :: (Environment m input, FormError input err)
=> Text
-> (input -> Either err a)
-> (FormId -> Maybe a -> view)
-> Maybe a
-> Form m input err view (Maybe a)
inputMaybe name = G.inputMaybe (getNamedFormId name)
inputNoData :: (Environment m input)
=> Text
-> (FormId -> view)
-> Form m input err view ()
inputNoData name = G.inputNoData (getNamedFormId name)
inputFile :: forall m input err view ft. (Environment m input, FormInput input, FormError input err, ft ~ FileType input, Monoid ft)
=> Text
-> (FormId -> view)
-> Form m input err view (FileType input)
inputFile name = G.inputFile (getNamedFormId name)
inputMulti :: forall m input err view a lbl. (FormError input err, FormInput input, Environment m input, Eq a)
=> Text
-> [(a, lbl)]
-> (input -> Either err [a])
-> (FormId -> [G.Choice lbl a] -> view)
-> (a -> Bool)
-> Form m input err view [a]
inputMulti name = G.inputMulti (getNamedFormId name)
inputChoice :: forall a m err input lbl view. (FormError input err, FormInput input, Environment m input, Eq a, Monoid view)
=> Text
-> (a -> Bool)
-> NonEmpty (a, lbl)
-> (input -> Either err a)
-> (FormId -> [G.Choice lbl a] -> view)
-> Form m input err view a
inputChoice name = G.inputChoice (getNamedFormId name)
inputList :: forall m input err a view. (Monad m, FormError input err, Environment m input)
=> Text
-> (input -> m (Either err [a]))
-> ([view] -> view)
-> [a]
-> view
-> (a -> Form m input err view a)
-> Form m input err view [a]
inputList name = G.inputList (getNamedFormId name)
label :: Environment m input
=> Text
-> (FormId -> view)
-> Form m input err view ()
label name = G.label (getNamedFormId name)
errors :: Environment m input
=> ([err] -> view)
-> Form m input err view ()
errors = G.errors
childErrors :: Environment m input
=> ([err] -> view)
-> Form m input err view ()
childErrors = G.childErrors
withErrors :: Environment m input
=> (view -> [err] -> view)
-> Form m input err view a
-> Form m input err view a
withErrors = G.withErrors
ireq :: forall m input view err a. (Monoid view, Environment m input, FormError input err)
=> Text
-> (input -> Either err a)
-> a
-> Form m input err view a
ireq name fromInput initialValue = Form (pure . fromInput) (pure initialValue) $ do
i <- getNamedFormId name
v <- getFormInput' i
case v of
Default -> pure
( mempty
, Ok ( Proved
{ pos = unitRange i
, unProved = initialValue
} )
)
Found inp -> case fromInput inp of
Right a -> pure
( mempty
, Ok ( Proved
{ pos = unitRange i
, unProved = a
} )
)
Left err -> pure
( mempty
, Error [(unitRange i, err)]
)
Missing -> pure
( mempty
, Error [(unitRange i, commonFormError (InputMissing i :: CommonFormError input) :: err)]
)
iopt :: forall m input view err a. (Monoid view, Environment m input, FormError input err)
=> Text
-> (input -> Either err a)
-> Maybe a
-> Form m input err view (Maybe a)
iopt name fromInput initialValue = Form (pure . fmap Just . fromInput) (pure initialValue) $ do
i <- getNamedFormId name
v <- getFormInput' i
case v of
Default -> pure
( mempty
, Ok ( Proved
{ pos = unitRange i
, unProved = initialValue
} )
)
Found inp -> case fromInput inp of
Right a -> pure
( mempty
, Ok ( Proved
{ pos = unitRange i
, unProved = Just a
} )
)
Left err -> pure
( mempty
, Error [(unitRange i, err)]
)
Missing -> pure
( mempty
, Ok ( Proved
{ pos = unitRange i
, unProved = Nothing
} )
)