Created
May 12, 2014 12:42
-
-
Save folsen/e3c3d37d3852e8823fbc to your computer and use it in GitHub Desktop.
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE OverloadedStrings #-} | |
module Main where | |
import Data.ByteString.Lazy.Char8 (pack) | |
import Web.Scotty as S | |
import Network.Wai.Middleware.RequestLogger | |
import Data.Aeson | |
import Data.Aeson.Types | |
import Control.Lens hiding ((.=), (??)) | |
import Data.Aeson.Lens | |
import qualified Data.Text as T | |
import Control.Error | |
import Control.Applicative | |
import qualified Data.HashMap.Strict as H | |
import Network.HTTP.Types | |
data TypeOne = TypeOne T.Text TypeTwo TypeThree | |
deriving (Show) | |
data TypeTwo = TypeTwo Double | |
deriving (Show) | |
data TypeThree = TypeThree Double | |
deriving (Show) | |
main :: IO () | |
main = scotty 3000 $ do | |
middleware logStdoutDev | |
post "/pdor" $ do | |
api_key <- param "api_key" | |
input <- param "input" | |
typeOne <- runEitherT $ do | |
result <- (decode (pack input) :: Maybe Value) ?? "Could not parse. Input JSON document is malformed" | |
typeTwoObj <- (result ^? key "typeTwo") ?? "Could not find key typeTwo in JSON document." | |
typeThreeObj <- (result ^? key "typeThree") ?? "Could not find key typeThree in JSON document." | |
name <- (result ^? key "name" . _String) ?? "Could not find key name in JSON document." | |
typeTwo <- hoistEither $ prependLeft "Error when parsing TypeTwo: " $ parseEither jsonTypeTwo typeTwoObj | |
typeThree <- hoistEither $ prependLeft "Error when parsing TypeThree: " $ parseEither jsonTypeThree typeThreeObj | |
return $ TypeOne name typeTwo typeThree | |
case typeOne of | |
Left errorMsg -> do | |
_ <- status badRequest400 | |
S.json $ object ["error" .= errorMsg] | |
Right _ -> | |
-- do something with the parsed Haskell type | |
S.json $ object ["api_key" .= (api_key :: String), "message" .= ("success" :: String)] | |
prependLeft :: String -> Either String a -> Either String a | |
prependLeft msg (Left s) = Left (msg ++ s) | |
prependLeft _ x = x | |
jsonTypeTwo :: Value -> Parser TypeTwo | |
jsonTypeTwo (Object v) = TypeTwo <$> v .: "val" | |
jsonTypeTwo _ = fail $ "no data present for TypeTwo" | |
jsonTypeThree :: Value -> Parser TypeThree | |
jsonTypeThree (Object v) = TypeThree <$> v .: "val" | |
jsonTypeThree _ = fail $ "no data present for TypeThree" |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment