module Text.Reform.Backend where
import Data.Maybe            (listToMaybe)
import           Data.Text   (Text)
import qualified Data.Text   as T
import Text.Reform.Result (FormId)
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 " ++ show 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 e where
    type ErrorInputType e
    commonFormError :: (CommonFormError (ErrorInputType e)) -> e
class FormInput input where
    
    
    type FileType input
    
    
    
    getInputString :: (FormError error, ErrorInputType error ~ input) => input -> Either error String
    getInputString input =
           case getInputStrings input of
             []  -> Left (commonFormError $ NoStringFound input)
             [s] -> Right s
             _   -> Left (commonFormError $ MultiStringsFound input)
    
    
    getInputStrings :: input -> [String]
    
    
    getInputText :: (FormError error, ErrorInputType error ~ input) => input -> Either error 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 error, ErrorInputType error ~ input) => input -> Either error (FileType input)