{-# LANGUAGE ScopedTypeVariables, TypeFamilies, ViewPatterns #-}
{- |
This module provides helper functions for HTML input elements. These helper functions are not specific to any particular web framework or html library.
-}
module Text.Reform.Generalized where
import Control.Applicative ((<$>))
import Control.Monad (foldM)
import Control.Monad.Trans (lift)
import qualified Data.IntSet as IS
import Data.List (find)
import Data.Maybe (mapMaybe)
import Numeric (readDec)
import Text.Reform.Backend
import Text.Reform.Core
import Text.Reform.Result
-- | used for constructing elements like @\@, which return a single input value.
input :: (Monad m, FormError error) =>
(input -> Either error a)
-> (FormId -> a -> view)
-> a
-> Form m input error view () a
input fromInput toView initialValue =
Form $ do i <- getFormId
v <- getFormInput' i
case v of
Default ->
return ( View $ const $ toView i initialValue
, return $ Ok (Proved { proofs = ()
, pos = unitRange i
, unProved = initialValue
}))
(Found (fromInput -> (Right a))) ->
return ( View $ const $ toView i a
, return $ Ok (Proved { proofs = ()
, pos = unitRange i
, unProved = a
}))
(Found (fromInput -> (Left error))) ->
return ( View $ const $ toView i initialValue
, return $ Error [(unitRange i, error)]
)
Missing ->
return ( View $ const $ toView i initialValue
, return $ Error [(unitRange i, commonFormError (InputMissing i))]
)
-- | used for elements like @\@ which are not always present in the form submission data.
inputMaybe :: (Monad m, FormError error) =>
(input -> Either error a)
-> (FormId -> a -> view)
-> a
-> Form m input error view () (Maybe a)
inputMaybe fromInput toView initialValue =
Form $ do i <- getFormId
v <- getFormInput' i
case v of
Default ->
return ( View $ const $ toView i initialValue
, return $ Ok (Proved { proofs = ()
, pos = unitRange i
, unProved = Just initialValue
}))
(Found (fromInput -> (Right a))) ->
return ( View $ const $ toView i a
, return $ Ok (Proved { proofs = ()
, pos = unitRange i
, unProved = (Just a)
}))
(Found (fromInput -> (Left error))) ->
return ( View $ const $ toView i initialValue
, return $ Error [(unitRange i, error)]
)
Missing ->
return ( View $ const $ toView i initialValue
, return $ Ok (Proved { proofs = ()
, pos = unitRange i
, unProved = Nothing
})
)
-- | used for elements like @\@ which take a value, but are never present in the form data set.
inputNoData :: (Monad m) =>
(FormId -> a -> view)
-> a
-> Form m input error view () ()
inputNoData toView a =
Form $ do i <- getFormId
return ( View $ const $ toView i a
, return $ Ok (Proved { proofs = ()
, pos = unitRange i
, unProved = ()
})
)
-- | used for @\@
inputFile :: forall m input error view. (Monad m, FormInput input, FormError error, ErrorInputType error ~ input) =>
(FormId -> view)
-> Form m input error view () (FileType input)
inputFile toView =
Form $ do i <- getFormId
v <- getFormInput' i
case v of
Default ->
return ( View $ const $ toView i
, return $ Error [(unitRange i, commonFormError (InputMissing i))]
)
(Found (getInputFile' -> (Right a))) ->
return ( View $ const $ toView i
, return $ Ok (Proved { proofs = ()
, pos = unitRange i
, unProved = a
}))
(Found (getInputFile' -> (Left error))) ->
return ( View $ const $ toView i
, return $ Error [(unitRange i, error)]
)
Missing ->
return ( View $ const $ toView i
, return $ Error [(unitRange i, commonFormError (InputMissing i))]
)
where
-- just here for the type-signature to make the type-checker happy
getInputFile' :: (FormError error, ErrorInputType error ~ input) => input -> Either error (FileType input)
getInputFile' = getInputFile
-- | used for groups of checkboxes, @\