{-# LANGUAGE GADTs, Rank2Types, RecordWildCards #-}
module Control.Monad.Script.Http (
Http()
, execHttpM
, HttpT()
, execHttpTM
, liftHttpT
, throwError
, throwJsonError
, throwHttpException
, throwIOException
, catchError
, catchJsonError
, catchHttpException
, catchIOException
, catchAnyError
, printError
, E()
, ask
, local
, reader
, R(..)
, basicEnv
, trivialEnv
, LogOptions(..)
, basicLogOptions
, trivialLogOptions
, logEntries
, LogSeverity(..)
, setLogSeverity
, W()
, printHttpLogs
, basicLogEntryPrinter
, gets
, modify
, S(..)
, basicState
, prompt
, P(..)
, evalIO
, evalMockIO
, comment
, wait
, logDebug
, logInfo
, logNotice
, logWarning
, logError
, logCritical
, logAlert
, logEmergency
, Control.Monad.Script.Http.hPutStrLn
, hPutStrLnBlocking
, httpGet
, httpSilentGet
, httpPost
, httpSilentPost
, httpDelete
, httpSilentDelete
, parseJson
, lookupKeyJson
, constructFromJson
, Url
, JsonError(..)
, HttpResponse(..)
, checkHttpM
, checkHttpTM
) where
import Prelude hiding (lookup)
import Control.Applicative
( Applicative(..), (<$>) )
import Control.Concurrent
( threadDelay )
import Control.Concurrent.MVar
( MVar, withMVar )
import Control.Exception
( IOException, Exception, try )
import Control.Monad
( Functor(..), Monad(..), ap )
import Control.Lens
( preview, (^.) )
import Data.Aeson
( Value(Object), Result(Success,Error), FromJSON, fromJSON, decode )
import Data.Aeson.Encode.Pretty
( encodePretty )
import Data.Aeson.Lens
( _Value )
import Data.ByteString.Lazy
( ByteString, fromStrict, readFile, writeFile )
import Data.ByteString.Lazy.Char8
( unpack, pack )
import Data.Functor.Identity
( Identity() )
import Data.HashMap.Strict
( lookup )
import Data.IORef
( IORef, newIORef, readIORef, writeIORef )
import Data.List
( intercalate )
import Data.String
( fromString )
import Data.Text
( Text )
import Data.Time
( UTCTime )
import Data.Time.Clock.System
( getSystemTime, systemToUTCTime )
import Data.Typeable
( Typeable )
import Data.Monoid
( Monoid(..) )
import Data.Semigroup
( Semigroup(..) )
import Network.HTTP.Client
( HttpException(..), CookieJar, HttpExceptionContent(StatusCodeException)
, Response, responseCookieJar, responseBody
, responseHeaders, responseVersion, responseStatus )
import Network.HTTP.Types
( HttpVersion, Status, ResponseHeaders )
import qualified Network.Wreq as Wreq
( Options, getWith, postWith, deleteWith, defaults, responseStatus, headers )
import qualified Network.Wreq.Session as S
( Session, newSession, getWith, postWith, deleteWith )
import System.IO
( Handle, hPutStrLn, hGetEcho, hSetEcho, hFlush
, hFlush, hGetLine, hPutStr, hPutChar, stdout )
import System.IO.Error
( ioeGetFileName, ioeGetLocation, ioeGetErrorString )
import Test.QuickCheck
( Property, Arbitrary(..), Gen )
import qualified Control.Monad.Script as S
import Network.HTTP.Client.Extras
import Data.Aeson.Extras
import Data.LogSeverity
import Data.MockIO
import Data.MockIO.FileSystem
newtype HttpT e r w s p m a = HttpT
{ httpT :: S.ScriptT (E e) (R e w r) (W e w) (S s) (P p) m a
} deriving Typeable
type Http e r w s p a = HttpT e r w s p Identity a
instance Functor (HttpT e r w s p m) where
fmap f = HttpT . fmap f . httpT
instance Applicative (HttpT e r w s p m) where
pure = return
(<*>) = ap
instance Monad (HttpT e r w s p m) where
return = HttpT . return
(HttpT x) >>= f = HttpT (x >>= (httpT . f))
execHttpTM
:: (Monad (m eff), Monad eff)
=> S s
-> R e w r
-> (forall u. P p u -> eff u)
-> (forall u. eff u -> m eff u)
-> HttpT e r w s p (m eff) t
-> m eff (Either (E e) t, S s, W e w)
execHttpTM s r p lift = S.execScriptTM s r p lift . httpT
checkHttpTM
:: (Monad (m eff), Monad eff)
=> S s
-> R e w r
-> (forall u. P p u -> eff u)
-> (forall u. eff u -> m eff u)
-> (m eff (Either (E e) t, S s, W e w) -> IO q)
-> (q -> Bool)
-> HttpT e r w s p (m eff) t
-> Property
checkHttpTM s r eval lift cond check =
S.checkScriptTM s r eval lift cond check . httpT
execHttpM
:: (Monad eff)
=> S s
-> R e w r
-> (forall u. P p u -> eff u)
-> Http e r w s p t
-> eff (Either (E e) t, S s, W e w)
execHttpM s r eval = S.execScriptM s r eval . httpT
checkHttpM
:: (Monad eff)
=> S s
-> R e w r
-> (forall u. P p u -> eff u)
-> (eff (Either (E e) t, S s, W e w) -> IO q)
-> (q -> Bool)
-> Http e r w s p t
-> Property
checkHttpM s r eval cond check =
S.checkScriptM s r eval cond check . httpT
ask
:: HttpT e r w s p m (R e w r)
ask = HttpT S.ask
local
:: (R e w r -> R e w r)
-> HttpT e r w s p m a
-> HttpT e r w s p m a
local f = HttpT . S.local f . httpT
transport
:: (R e w r2 -> R e w r1)
-> HttpT e r1 w s p m a
-> HttpT e r2 w s p m a
transport f = HttpT . S.transport f . httpT
reader
:: (R e w r -> a)
-> HttpT e r w s p m a
reader f = HttpT (S.reader f)
get
:: HttpT e r w s p m (S s)
get = HttpT S.get
put
:: S s
-> HttpT e r w s p m ()
put s = HttpT (S.put s)
modify
:: (S s -> S s)
-> HttpT e r w s p m ()
modify f = HttpT (S.modify' f)
gets
:: (S s -> a)
-> HttpT e r w s p m a
gets f = HttpT (S.gets f)
tell
:: W e w
-> HttpT e r w s p m ()
tell w = HttpT (S.tell w)
pass
:: HttpT e r w s p m (a, W e w -> W e w)
-> HttpT e r w s p m a
pass = HttpT . S.pass . httpT
censor
:: (W e w -> W e w)
-> HttpT e r w s p m a
-> HttpT e r w s p m a
censor f = HttpT . S.censor f . httpT
except
:: Either (E e) a
-> HttpT e r w s p m a
except e = HttpT (S.except e)
throw
:: E e
-> HttpT e r w s p m a
throw e = HttpT (S.throw e)
catch
:: HttpT e r w s p m a
-> (E e -> HttpT e r w s p m a)
-> HttpT e r w s p m a
catch x f = HttpT (S.catch (httpT x) (httpT . f))
prompt
:: P p a
-> HttpT e r w s p m a
prompt p = HttpT (S.prompt p)
liftHttpT
:: (Monad m)
=> m a
-> HttpT e r w s p m a
liftHttpT = HttpT . S.lift
data E e
= E_Http HttpException
| E_IO IOException
| E_Json JsonError
| E e
printError :: (e -> String) -> E e -> String
printError p err = case err of
E_Http e -> unlines [ "HTTP Exception:", show e ]
E_IO e -> unlines [ "IO Exception:", show e ]
E_Json e -> unlines [ "JSON Error:", show e ]
E e -> unlines [ "Error:", p e ]
throwHttpException
:: HttpException
-> HttpT e r w s p m a
throwHttpException e = do
logNow LogError $ errorMessage $ E_Http e
throw $ E_Http e
catchHttpException
:: HttpT e r w s p m a
-> (HttpException -> HttpT e r w s p m a)
-> HttpT e r w s p m a
catchHttpException x handler = catch x $ \err ->
case err of
E_Http e -> handler e
_ -> throw err
throwIOException
:: IOException
-> HttpT e r w s p m a
throwIOException e = do
logNow LogError $ errorMessage $ E_IO e
throw $ E_IO e
catchIOException
:: HttpT e r w s p m a
-> (IOException -> HttpT e r w s p m a)
-> HttpT e r w s p m a
catchIOException x handler = catch x $ \err ->
case err of
E_IO e -> handler e
_ -> throw err
throwJsonError
:: JsonError
-> HttpT e r w s p m a
throwJsonError e = do
logNow LogError $ errorMessage $ E_Json e
throw $ E_Json e
catchJsonError
:: HttpT e r w s p m a
-> (JsonError -> HttpT e r w s p m a)
-> HttpT e r w s p m a
catchJsonError x handler = catch x $ \err ->
case err of
E_Json e -> handler e
_ -> throw err
throwError
:: e
-> HttpT e r w s p m a
throwError e = do
logNow LogError $ errorMessage $ E e
throw $ E e
catchError
:: HttpT e r w s p m a
-> (e -> HttpT e r w s p m a)
-> HttpT e r w s p m a
catchError x handler = catch x $ \err ->
case err of
E e -> handler e
_ -> throw err
catchAnyError
:: HttpT e r w s p m a
-> (e -> HttpT e r w s p m a)
-> (HttpException -> HttpT e r w s p m a)
-> (IOException -> HttpT e r w s p m a)
-> (JsonError -> HttpT e r w s p m a)
-> HttpT e r w s p m a
catchAnyError x hE hHttp hIO hJson =
catch x $ \err -> case err of
E e -> hE e
E_Http e -> hHttp e
E_IO e -> hIO e
E_Json e -> hJson e
data R e w r = R
{ _logOptions :: LogOptions e w
, _logEntryPrinter :: LogOptions e w -> LogEntry e w -> Maybe String
, _logHandle :: Handle
, _logLock :: Maybe (MVar ())
, _uid :: String
, _httpErrorInject :: HttpException -> Maybe e
, _env :: r
}
basicEnv
:: (Show e, Show w)
=> r
-> R e w r
basicEnv r = R
{ _httpErrorInject = const Nothing
, _logOptions = basicLogOptions
, _logEntryPrinter = basicLogEntryPrinter
, _logHandle = stdout
, _logLock = Nothing
, _uid = ""
, _env = r
}
trivialEnv
:: r
-> R e w r
trivialEnv r = R
{ _httpErrorInject = const Nothing
, _logOptions = trivialLogOptions
, _logEntryPrinter = basicLogEntryPrinter
, _logHandle = stdout
, _logLock = Nothing
, _uid = ""
, _env = r
}
data LogOptions e w = LogOptions
{
_logColor :: Bool
, _logJson :: Bool
, _logSilent :: Bool
, _logMinSeverity :: LogSeverity
, _logHeaders :: Bool
, _printUserError :: Bool -> e -> String
, _printUserLog :: Bool -> w -> String
}
basicLogOptions :: (Show e, Show w) => LogOptions e w
basicLogOptions = LogOptions
{ _logColor = True
, _logJson = False
, _logSilent = False
, _logMinSeverity = LogDebug
, _logHeaders = True
, _printUserError = \_ e -> show e
, _printUserLog = \_ w -> show w
}
trivialLogOptions :: LogOptions e w
trivialLogOptions = LogOptions
{ _logColor = True
, _logJson = False
, _logSilent = False
, _logMinSeverity = LogDebug
, _logHeaders = True
, _printUserError = \_ _ -> "ERROR"
, _printUserLog = \_ _ -> "LOG"
}
basicLogEntryPrinter
:: LogOptions e w
-> LogEntry e w
-> Maybe String
basicLogEntryPrinter opt@LogOptions{..} LogEntry{..} =
if _logSilent || (_logEntrySeverity < _logMinSeverity)
then Nothing
else
let
colorize msg = if _logColor
then colorBySeverity _logEntrySeverity msg
else msg
timestamp :: String
timestamp = take 19 $ show _logEntryTimestamp
in
Just $ unwords $ filter (/= "")
[ colorize timestamp
, _logEntryUID
, logEntryTitle _logEntry
, logEntryBody opt _logEntry
]
newtype W e w = W
{ unW :: [LogEntry e w]
} deriving Show
instance Semigroup (W e w) where
(W a1) <> (W a2) = W (a1 ++ a2)
instance Monoid (W e w) where
mempty = W []
mappend = (<>)
data LogEntry e w = LogEntry
{ _logEntryTimestamp :: UTCTime
, _logEntryUID :: String
, _logEntrySeverity :: LogSeverity
, _logEntry :: Log e w
} deriving Show
data Log e w
= L_Comment String
| L_Request HttpVerb Url Wreq.Options (Maybe ByteString)
| L_SilentRequest
| L_Response HttpResponse
| L_SilentResponse
| L_Pause Int
| L_HttpError HttpException
| L_IOError IOException
| L_JsonError JsonError
| L_Error e
| L_Log w
deriving Show
logEntryTitle :: Log e w -> LogEntryTitle
logEntryTitle e = case e of
L_Comment _ -> "Comment"
L_Request _ _ _ _ -> "Request"
L_SilentRequest -> "Silent Request"
L_Response _ -> "Response"
L_SilentResponse -> "Silent Response"
L_Pause _ -> "Pause"
L_HttpError _ -> "HTTP Exception"
L_IOError _ -> "IO Exception"
L_JsonError _ -> "JSON Error"
L_Error _ -> "Error"
L_Log _ -> "Log"
data HttpVerb
= DELETE | GET | POST
deriving (Eq, Show)
printHttpLogs
:: Handle
-> Maybe (MVar ())
-> LogOptions e w
-> (LogOptions e w -> LogEntry e w -> Maybe String)
-> W e w
-> IO ()
printHttpLogs handle lock opts printer (W ws) = do
let
printEntry w =
case printer opts w of
Nothing -> return ()
Just str -> do
case lock of
Just lock -> withMVar lock (\() -> System.IO.hPutStrLn handle str)
Nothing -> System.IO.hPutStrLn handle str
hFlush handle
if _logSilent opts
then return ()
else mapM_ printEntry ws
errorMessage :: E e -> Log e w
errorMessage e = case e of
E_Http err -> L_HttpError err
E_IO err -> L_IOError err
E_Json err -> L_JsonError err
E e -> L_Error e
type LogEntryTitle = String
type LogEntryBody = String
logEntryBody
:: LogOptions e w
-> Log e w
-> LogEntryBody
logEntryBody LogOptions{..} entry = case entry of
L_Comment msg -> msg
L_Request verb url opt payload ->
let
head = case (_logJson, _logHeaders) of
(True, True) -> unpack $ encodePretty $ jsonResponseHeaders $ opt ^. Wreq.headers
(False, True) -> show $ opt ^. Wreq.headers
(_, False) -> ""
body = case (_logJson, payload) of
(True, Just p) -> case decode p of
Nothing -> "JSON parse error:\n" ++ unpack p
Just v -> unpack $ encodePretty (v :: Value)
(False, Just p) -> unpack p
(_, Nothing) -> ""
in
intercalate "\n" $ filter (/= "") [unwords ["Request", show verb, url], head, body]
L_SilentRequest -> ""
L_Response response ->
let
head = case (_logJson, _logHeaders) of
(True, True) -> unpack $ encodePretty $ jsonResponseHeaders $ _responseHeaders response
(False, True) -> show $ _responseHeaders response
(_, False) -> ""
body = case _logJson of
True -> unpack $ encodePretty $ preview _Value $ _responseBody response
False -> show response
in
intercalate "\n" $ filter (/= "") ["Response", head, body]
L_SilentResponse -> ""
L_Pause k -> "Wait for " ++ show k ++ "μs"
L_HttpError e -> if _logJson
then
let
unpackHttpError :: HttpException -> Maybe (String, String)
unpackHttpError err = case err of
HttpExceptionRequest _ (StatusCodeException s r) -> do
json <- decode $ fromStrict r
let status = s ^. Wreq.responseStatus
return (show status, unpack $ encodePretty (json :: Value))
_ -> Nothing
in
case unpackHttpError e of
Nothing -> show e
Just (code, json) -> intercalate "\n" [ unwords [ "HTTP Error Response", code], json ]
else show e
L_IOError e -> unwords [ show $ ioeGetFileName e, ioeGetLocation e, ioeGetErrorString e ]
L_JsonError e -> show e
L_Error e -> unwords [ _printUserError _logJson e ]
L_Log w -> unwords [ _printUserLog _logJson w ]
logEntries :: W e w -> [w]
logEntries (W xs) = entries xs
where
entries [] = []
entries (w:ws) = case _logEntry w of
L_Log u -> u : entries ws
_ -> entries ws
data S s = S
{ _httpOptions :: Wreq.Options
, _httpSession :: Maybe S.Session
, _userState :: s
}
basicState :: s -> S s
basicState s = S
{ _httpOptions = Wreq.defaults
, _httpSession = Nothing
, _userState = s
}
data P p a where
HPutStrLn
:: Handle -> String
-> P p (Either IOException ())
HPutStrLnBlocking
:: MVar () -> Handle -> String
-> P p (Either IOException ())
GetSystemTime :: P p UTCTime
ThreadDelay :: Int -> P p ()
HttpGet
:: Wreq.Options -> Maybe S.Session -> Url
-> P p (Either HttpException HttpResponse)
HttpPost
:: Wreq.Options -> Maybe S.Session -> Url
-> ByteString -> P p (Either HttpException HttpResponse)
HttpDelete
:: Wreq.Options -> Maybe S.Session -> Url
-> P p (Either HttpException HttpResponse)
P :: p a -> P p a
evalIO
:: (p a -> IO a)
-> P p a
-> IO a
evalIO eval x = case x of
HPutStrLn handle string -> try $ do
System.IO.hPutStrLn handle string
hFlush handle
HPutStrLnBlocking lock handle str -> try $ do
withMVar lock (\() -> System.IO.hPutStrLn handle str)
hFlush handle
GetSystemTime -> fmap systemToUTCTime getSystemTime
ThreadDelay k -> threadDelay k
HttpGet opts s url -> case s of
Nothing -> try $ readHttpResponse <$> Wreq.getWith opts url
Just sn -> try $ readHttpResponse <$> S.getWith opts sn url
HttpPost opts s url msg -> case s of
Nothing -> try $ readHttpResponse <$> Wreq.postWith opts url msg
Just sn -> try $ readHttpResponse <$> S.postWith opts sn url msg
HttpDelete opts s url -> case s of
Nothing -> try $ readHttpResponse <$> Wreq.deleteWith opts url
Just sn -> try $ readHttpResponse <$> S.deleteWith opts sn url
P act -> eval act
evalMockIO
:: (p a -> MockIO s a)
-> P p a
-> MockIO s a
evalMockIO eval x = case x of
HPutStrLn handle str -> do
incrementTimer 1
fmap Right $ modifyMockWorld $ \w -> w
{ _files = appendLines (Right handle) (lines str) $ _files w }
HPutStrLnBlocking _ handle str -> do
incrementTimer 1
fmap Right $ modifyMockWorld $ \w -> w
{ _files = appendLines (Right handle) (lines str) $ _files w }
GetSystemTime -> do
incrementTimer 1
MockWorld{..} <- getMockWorld
return _time
ThreadDelay k -> incrementTimer k
HttpGet _ _ url -> do
incrementTimer 1
MockWorld{..} <- getMockWorld
let (r,t) = unMockNetwork (_httpGet url) _serverState
modifyMockWorld $ \w -> w { _serverState = t }
return r
HttpPost _ _ url payload -> do
incrementTimer 1
MockWorld{..} <- getMockWorld
let (r,t) = unMockNetwork (_httpPost url payload) _serverState
modifyMockWorld $ \w -> w { _serverState = t }
return r
HttpDelete _ _ url -> do
incrementTimer 1
MockWorld{..} <- getMockWorld
let (r,t) = unMockNetwork (_httpDelete url) _serverState
modifyMockWorld $ \w -> w { _serverState = t }
return r
P p -> do
incrementTimer 1
eval p
logNow
:: LogSeverity
-> Log e w
-> HttpT e r w s p m ()
logNow severity msg = do
time <- prompt GetSystemTime
printer <- reader _logEntryPrinter
R{..} <- ask
case printer _logOptions (LogEntry time _uid severity msg) of
Nothing -> return ()
Just str -> case _logLock of
Just lock -> hPutStrLnBlocking lock _logHandle str
Nothing -> Control.Monad.Script.Http.hPutStrLn _logHandle str
tell $ W [LogEntry time _uid severity msg]
comment
:: String
-> HttpT e r w s p m ()
comment msg = logNow LogInfo $ L_Comment msg
wait
:: Int
-> HttpT e r w s p m ()
wait k = do
logNow LogInfo $ L_Pause k
prompt $ ThreadDelay k
logEntry :: LogSeverity -> w -> HttpT e r w s p m ()
logEntry severity = logNow severity . L_Log
logDebug :: w -> HttpT e r w s p m ()
logDebug = logEntry LogDebug
logInfo :: w -> HttpT e r w s p m ()
logInfo = logEntry LogInfo
logNotice :: w -> HttpT e r w s p m ()
logNotice = logEntry LogNotice
logWarning :: w -> HttpT e r w s p m ()
logWarning = logEntry LogWarning
logError :: w -> HttpT e r w s p m ()
logError = logEntry LogError
logCritical :: w -> HttpT e r w s p m ()
logCritical = logEntry LogCritical
logAlert :: w -> HttpT e r w s p m ()
logAlert = logEntry LogAlert
logEmergency :: w -> HttpT e r w s p m ()
logEmergency = logEntry LogEmergency
setLogSeverity
:: LogSeverity
-> HttpT e r w s p m a
-> HttpT e r w s p m a
setLogSeverity severity = censor (W . map f . unW)
where
f :: LogEntry e w -> LogEntry e w
f e = e { _logEntrySeverity = severity }
hPutStrLn
:: Handle
-> String
-> HttpT e r w s p m ()
hPutStrLn h str = do
result <- prompt $ HPutStrLn h str
case result of
Right () -> return ()
Left e -> throwIOException e
hPutStrLnBlocking
:: MVar ()
-> Handle
-> String
-> HttpT e r w s p m ()
hPutStrLnBlocking lock h str = do
result <- prompt $ HPutStrLnBlocking lock h str
case result of
Right () -> return ()
Left e -> throwIOException e
httpGet
:: Url
-> HttpT e r w s p m HttpResponse
httpGet url = do
R{..} <- ask
S{..} <- get
logNow LogDebug $ L_Request GET url _httpOptions Nothing
result <- prompt $ HttpGet _httpOptions _httpSession url
case result of
Right response -> do
logNow LogDebug $ L_Response response
return response
Left err -> case _httpErrorInject err of
Just z -> throwError z
Nothing -> throwHttpException err
httpSilentGet
:: Url
-> HttpT e r w s p m HttpResponse
httpSilentGet url = do
R{..} <- ask
S{..} <- get
logNow LogDebug L_SilentRequest
result <- prompt $ HttpGet _httpOptions _httpSession url
case result of
Right response -> do
logNow LogDebug L_SilentResponse
return response
Left err -> case _httpErrorInject err of
Just z -> throwError z
Nothing -> throwHttpException err
httpPost
:: Url
-> ByteString
-> HttpT e r w s p m HttpResponse
httpPost url payload = do
R{..} <- ask
S{..} <- get
logNow LogDebug $ L_Request POST url _httpOptions (Just payload)
result <- prompt $ HttpPost _httpOptions _httpSession url payload
case result of
Right response -> do
logNow LogDebug $ L_Response response
return response
Left err -> case _httpErrorInject err of
Just z -> throwError z
Nothing -> throwHttpException err
httpSilentPost
:: Url
-> ByteString
-> HttpT e r w s p m HttpResponse
httpSilentPost url payload = do
R{..} <- ask
S{..} <- get
logNow LogDebug L_SilentRequest
result <- prompt $ HttpPost _httpOptions _httpSession url payload
case result of
Right response -> do
logNow LogDebug L_SilentResponse
return response
Left err -> case _httpErrorInject err of
Just z -> throwError z
Nothing -> throwHttpException err
httpDelete
:: Url
-> HttpT e r w s p m HttpResponse
httpDelete url = do
R{..} <- ask
S{..} <- get
logNow LogDebug $ L_Request DELETE url _httpOptions Nothing
result <- prompt $ HttpDelete _httpOptions _httpSession url
case result of
Right response -> do
logNow LogDebug$ L_Response response
return response
Left err -> case _httpErrorInject err of
Just z -> throwError z
Nothing -> throwHttpException err
httpSilentDelete
:: Url
-> HttpT e r w s p m HttpResponse
httpSilentDelete url = do
R{..} <- ask
S{..} <- get
logNow LogDebug L_SilentRequest
result <- prompt $ HttpDelete _httpOptions _httpSession url
case result of
Right response -> do
logNow LogDebug L_SilentResponse
return response
Left err -> case _httpErrorInject err of
Just z -> throwError z
Nothing -> throwHttpException err
parseJson
:: ByteString
-> HttpT e r w s p m Value
parseJson bytes = case preview _Value bytes of
Just value -> return value
Nothing -> throwJsonError $ JsonParseError bytes
lookupKeyJson
:: Text
-> Value
-> HttpT e r w s p m Value
lookupKeyJson key v = case v of
Object obj -> case lookup key obj of
Nothing -> throwJsonError $ JsonKeyDoesNotExist key (Object obj)
Just value -> return value
_ -> throwJsonError $ JsonKeyLookupOffObject key v
constructFromJson
:: (FromJSON a)
=> Value
-> HttpT e r w s p m a
constructFromJson value = case fromJSON value of
Success x -> return x
Error msg -> throwJsonError $ JsonConstructError msg