module Data.Factual.Write.Flag
(
Flag(..)
, Problem(..)
, module Data.Factual.Shared.Table
) where
import Data.Factual.Write
import Data.Factual.Shared.Table
import Data.Maybe (fromJust)
import Data.Factual.Utils
import qualified Data.Map as M
data Problem = Duplicate
| Nonexistent
| Inaccurate
| Inappropriate
| Spam
| Other
deriving (Eq, Show)
data Flag = Flag { table :: Table
, factualId :: String
, problem :: Problem
, user :: String
, comment :: Maybe String
, debug :: Bool
, reference :: Maybe String
} deriving (Eq, Show)
instance Write Flag where
path flag = (show $ table flag) ++ "/" ++ (factualId flag) ++ "/flag"
params _ = M.empty
body flag = M.fromList [ ("problem", show $ problem flag)
, ("user", user flag)
, commentPair flag
, debugPair flag
, referencePair flag ]
commentPair :: Flag -> (String, String)
commentPair flag
| comment flag == Nothing = ("comment", "")
| otherwise = ("comment", fromJust $ comment flag)
debugPair :: Flag -> (String, String)
debugPair flag
| debug flag == True = ("debug", "true")
| otherwise = ("debug", "false")
referencePair :: Flag -> (String, String)
referencePair flag
| reference flag == Nothing = ("reference", "")
| otherwise = ("reference", fromJust $ reference flag)