{-# LANGUAGE
MultiParamTypeClasses
, TypeFamilies
, OverloadedStrings
, FunctionalDependencies
#-}
module Ditto.Backend where
import Data.Text (Text)
import Ditto.Types (FormId, encodeFormId)
import qualified Data.Text as T
data CommonFormError input
= InputMissing FormId
| NoStringFound input
| NoFileFound input
| MultiFilesFound input
| MultiStringsFound input
| MissingDefaultValue
deriving (Eq, Ord, Show)
commonFormErrorStr
:: (input -> String)
-> CommonFormError input
-> String
commonFormErrorStr showInput cfe = case cfe of
InputMissing formId -> "Input field missing for " ++ (T.unpack . encodeFormId) formId
NoStringFound input -> "Could not extract a string value from: " ++ showInput input
NoFileFound input -> "Could not find a file associated with: " ++ showInput input
MultiFilesFound input -> "Found multiple files associated with: " ++ showInput input
MultiStringsFound input -> "Found multiple strings associated with: " ++ showInput input
MissingDefaultValue -> "Missing default value."
commonFormErrorText
:: (input -> Text)
-> CommonFormError input
-> Text
commonFormErrorText showInput cfe = case cfe of
InputMissing formId -> "Input field missing for " <> encodeFormId formId
NoStringFound input -> "Could not extract a string value from: " <> showInput input
NoFileFound input -> "Could not find a file associated with: " <> showInput input
MultiFilesFound input -> "Found multiple files associated with: " <> showInput input
MultiStringsFound input -> "Found multiple strings associated with: " <> showInput input
MissingDefaultValue -> "Missing default value."
class FormError input err where
commonFormError :: CommonFormError input -> err
instance FormError Text Text where
commonFormError = commonFormErrorText id
class FormInput input where
type FileType input
getInputString :: (FormError input err) => input -> Either err String
getInputString input =
case getInputStrings input of
[] -> Left (commonFormError $ NoStringFound input)
[s] -> Right s
_ -> Left (commonFormError $ MultiStringsFound input)
getInputStrings :: input -> [String]
getInputStrings = map T.unpack . getInputTexts
getInputText :: (FormError input err) => input -> Either err Text
getInputText input =
case getInputTexts input of
[] -> Left (commonFormError $ NoStringFound input)
[s] -> Right s
_ -> Left (commonFormError $ MultiStringsFound input)
getInputTexts :: input -> [Text]
getInputTexts = map T.pack . getInputStrings
getInputFile :: (FormError input err) => input -> Either err (FileType input)