{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Database.Bloodhound.Internal.Client.BHRequest
(
BHRequest (..),
StatusIndependant,
StatusDependant,
mkFullRequest,
mkSimpleRequest,
ParsedEsResponse,
ParseBHResponse (..),
Server (..),
Endpoint (..),
mkEndpoint,
withQueries,
getEndpoint,
withBHResponse,
withBHResponse_,
withBHResponseParsedEsResponse,
keepBHResponse,
joinBHResponse,
BHResponse (..),
decodeResponse,
eitherDecodeResponse,
parseEsResponse,
parseEsResponseWith,
isVersionConflict,
isSuccess,
isCreated,
statusCodeIs,
EsProtocolException (..),
EsResult (..),
EsResultFound (..),
EsError (..),
Acknowledged (..),
Accepted (..),
IgnoredBody (..),
)
where
import qualified Blaze.ByteString.Builder as BB
import Control.Applicative as A
import Control.Monad
import Control.Monad.Catch
import Data.Aeson
import qualified Data.ByteString.Lazy as BL
import Data.Ix
import Data.Monoid
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import Data.Typeable
import Database.Bloodhound.Internal.Client.Doc
import GHC.Exts
import Network.HTTP.Client
import qualified Network.HTTP.Types.Method as NHTM
import qualified Network.HTTP.Types.Status as NHTS
import qualified Network.HTTP.Types.URI as NHTU
import Prelude hiding (filter, head)
newtype Server = Server Text
deriving stock (Server -> Server -> Bool
(Server -> Server -> Bool)
-> (Server -> Server -> Bool) -> Eq Server
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Server -> Server -> Bool
== :: Server -> Server -> Bool
$c/= :: Server -> Server -> Bool
/= :: Server -> Server -> Bool
Eq, Int -> Server -> ShowS
[Server] -> ShowS
Server -> String
(Int -> Server -> ShowS)
-> (Server -> String) -> ([Server] -> ShowS) -> Show Server
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Server -> ShowS
showsPrec :: Int -> Server -> ShowS
$cshow :: Server -> String
show :: Server -> String
$cshowList :: [Server] -> ShowS
showList :: [Server] -> ShowS
Show)
deriving newtype (Maybe Server
Value -> Parser [Server]
Value -> Parser Server
(Value -> Parser Server)
-> (Value -> Parser [Server]) -> Maybe Server -> FromJSON Server
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Server
parseJSON :: Value -> Parser Server
$cparseJSONList :: Value -> Parser [Server]
parseJSONList :: Value -> Parser [Server]
$comittedField :: Maybe Server
omittedField :: Maybe Server
FromJSON)
data Endpoint = Endpoint
{ Endpoint -> [Text]
getRawEndpoint :: [Text],
Endpoint -> [(Text, Maybe Text)]
getRawEndpointQueries :: [(Text, Maybe Text)]
}
deriving stock (Endpoint -> Endpoint -> Bool
(Endpoint -> Endpoint -> Bool)
-> (Endpoint -> Endpoint -> Bool) -> Eq Endpoint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Endpoint -> Endpoint -> Bool
== :: Endpoint -> Endpoint -> Bool
$c/= :: Endpoint -> Endpoint -> Bool
/= :: Endpoint -> Endpoint -> Bool
Eq, Int -> Endpoint -> ShowS
[Endpoint] -> ShowS
Endpoint -> String
(Int -> Endpoint -> ShowS)
-> (Endpoint -> String) -> ([Endpoint] -> ShowS) -> Show Endpoint
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Endpoint -> ShowS
showsPrec :: Int -> Endpoint -> ShowS
$cshow :: Endpoint -> String
show :: Endpoint -> String
$cshowList :: [Endpoint] -> ShowS
showList :: [Endpoint] -> ShowS
Show)
instance IsList Endpoint where
type Item Endpoint = Text
toList :: Endpoint -> [Item Endpoint]
toList = Endpoint -> [Text]
Endpoint -> [Item Endpoint]
getRawEndpoint
fromList :: [Item Endpoint] -> Endpoint
fromList = [Text] -> Endpoint
[Item Endpoint] -> Endpoint
mkEndpoint
mkEndpoint :: [Text] -> Endpoint
mkEndpoint :: [Text] -> Endpoint
mkEndpoint [Text]
urlParts = [Text] -> [(Text, Maybe Text)] -> Endpoint
Endpoint [Text]
urlParts [(Text, Maybe Text)]
forall a. Monoid a => a
mempty
getEndpoint :: Server -> Endpoint -> Text
getEndpoint :: Server -> Endpoint -> Text
getEndpoint (Server Text
serverRoot) Endpoint
endpoint =
Text -> [Text] -> Text
T.intercalate Text
"/" (Text
serverRoot Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: Endpoint -> [Text]
getRawEndpoint Endpoint
endpoint) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
queries
where
queries :: Text
queries = ByteString -> Text
T.decodeUtf8 (ByteString -> Text) -> ByteString -> Text
forall a b. (a -> b) -> a -> b
$ Builder -> ByteString
BB.toByteString (Builder -> ByteString) -> Builder -> ByteString
forall a b. (a -> b) -> a -> b
$ Bool -> [(Text, Maybe Text)] -> Builder
NHTU.renderQueryText Bool
prependQuestionMark ([(Text, Maybe Text)] -> Builder)
-> [(Text, Maybe Text)] -> Builder
forall a b. (a -> b) -> a -> b
$ Endpoint -> [(Text, Maybe Text)]
getRawEndpointQueries Endpoint
endpoint
prependQuestionMark :: Bool
prependQuestionMark = Bool
True
withQueries :: Endpoint -> [(Text, Maybe Text)] -> Endpoint
withQueries :: Endpoint -> [(Text, Maybe Text)] -> Endpoint
withQueries Endpoint
endpoint [(Text, Maybe Text)]
queries = Endpoint
endpoint {getRawEndpointQueries = getRawEndpointQueries endpoint <> queries}
data BHRequest parsingContext responseBody = BHRequest
{ forall parsingContext responseBody.
BHRequest parsingContext responseBody -> ByteString
bhRequestMethod :: NHTM.Method,
forall parsingContext responseBody.
BHRequest parsingContext responseBody -> Endpoint
bhRequestEndpoint :: Endpoint,
forall parsingContext responseBody.
BHRequest parsingContext responseBody -> Maybe ByteString
bhRequestBody :: Maybe BL.ByteString,
forall parsingContext responseBody.
BHRequest parsingContext responseBody
-> BHResponse parsingContext responseBody
-> Either EsProtocolException (ParsedEsResponse responseBody)
bhRequestParser :: BHResponse parsingContext responseBody -> Either EsProtocolException (ParsedEsResponse responseBody)
}
instance Functor (BHRequest parsingContext) where
fmap :: forall a b.
(a -> b)
-> BHRequest parsingContext a -> BHRequest parsingContext b
fmap a -> b
f BHRequest parsingContext a
req =
BHRequest parsingContext a
req
{ bhRequestParser =
\BHResponse {Response ByteString
getResponse :: Response ByteString
getResponse :: forall parsingContext body.
BHResponse parsingContext body -> Response ByteString
..} -> (Either EsError a -> ParsedEsResponse b)
-> Either EsProtocolException (Either EsError a)
-> Either EsProtocolException (ParsedEsResponse b)
forall a b.
(a -> b)
-> Either EsProtocolException a -> Either EsProtocolException b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> Either EsError a -> ParsedEsResponse b
forall a b. (a -> b) -> Either EsError a -> Either EsError b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) (Either EsProtocolException (Either EsError a)
-> Either EsProtocolException (ParsedEsResponse b))
-> Either EsProtocolException (Either EsError a)
-> Either EsProtocolException (ParsedEsResponse b)
forall a b. (a -> b) -> a -> b
$ BHRequest parsingContext a
-> BHResponse parsingContext a
-> Either EsProtocolException (Either EsError a)
forall parsingContext responseBody.
BHRequest parsingContext responseBody
-> BHResponse parsingContext responseBody
-> Either EsProtocolException (ParsedEsResponse responseBody)
bhRequestParser BHRequest parsingContext a
req (BHResponse parsingContext a
-> Either EsProtocolException (Either EsError a))
-> BHResponse parsingContext a
-> Either EsProtocolException (Either EsError a)
forall a b. (a -> b) -> a -> b
$ BHResponse {Response ByteString
getResponse :: Response ByteString
getResponse :: Response ByteString
..}
}
data StatusIndependant
data StatusDependant
mkFullRequest :: (ParseBHResponse parsingContext, FromJSON responseBody) => NHTM.Method -> Endpoint -> BL.ByteString -> BHRequest parsingContext responseBody
mkFullRequest :: forall parsingContext responseBody.
(ParseBHResponse parsingContext, FromJSON responseBody) =>
ByteString
-> Endpoint -> ByteString -> BHRequest parsingContext responseBody
mkFullRequest ByteString
method' Endpoint
endpoint ByteString
body =
BHRequest
{ bhRequestMethod :: ByteString
bhRequestMethod = ByteString
method',
bhRequestEndpoint :: Endpoint
bhRequestEndpoint = Endpoint
endpoint,
bhRequestBody :: Maybe ByteString
bhRequestBody = ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
body,
bhRequestParser :: BHResponse parsingContext responseBody
-> Either EsProtocolException (ParsedEsResponse responseBody)
bhRequestParser = BHResponse parsingContext responseBody
-> Either EsProtocolException (ParsedEsResponse responseBody)
forall a.
FromJSON a =>
BHResponse parsingContext a
-> Either EsProtocolException (ParsedEsResponse a)
forall parsingContext a.
(ParseBHResponse parsingContext, FromJSON a) =>
BHResponse parsingContext a
-> Either EsProtocolException (ParsedEsResponse a)
parseBHResponse
}
mkSimpleRequest :: (ParseBHResponse parsingContext, FromJSON responseBody) => NHTM.Method -> Endpoint -> BHRequest parsingContext responseBody
mkSimpleRequest :: forall parsingContext responseBody.
(ParseBHResponse parsingContext, FromJSON responseBody) =>
ByteString -> Endpoint -> BHRequest parsingContext responseBody
mkSimpleRequest ByteString
method' Endpoint
endpoint =
BHRequest
{ bhRequestMethod :: ByteString
bhRequestMethod = ByteString
method',
bhRequestEndpoint :: Endpoint
bhRequestEndpoint = Endpoint
endpoint,
bhRequestBody :: Maybe ByteString
bhRequestBody = Maybe ByteString
forall a. Maybe a
Nothing,
bhRequestParser :: BHResponse parsingContext responseBody
-> Either EsProtocolException (ParsedEsResponse responseBody)
bhRequestParser = BHResponse parsingContext responseBody
-> Either EsProtocolException (ParsedEsResponse responseBody)
forall a.
FromJSON a =>
BHResponse parsingContext a
-> Either EsProtocolException (ParsedEsResponse a)
forall parsingContext a.
(ParseBHResponse parsingContext, FromJSON a) =>
BHResponse parsingContext a
-> Either EsProtocolException (ParsedEsResponse a)
parseBHResponse
}
class ParseBHResponse parsingContext where
parseBHResponse ::
(FromJSON a) =>
BHResponse parsingContext a ->
Either EsProtocolException (ParsedEsResponse a)
instance ParseBHResponse StatusDependant where
parseBHResponse :: forall a.
FromJSON a =>
BHResponse StatusDependant a
-> Either EsProtocolException (ParsedEsResponse a)
parseBHResponse = BHResponse StatusDependant a
-> Either EsProtocolException (ParsedEsResponse a)
forall body parsingContext.
FromJSON body =>
BHResponse parsingContext body
-> Either EsProtocolException (ParsedEsResponse body)
parseEsResponse
instance ParseBHResponse StatusIndependant where
parseBHResponse :: forall a.
FromJSON a =>
BHResponse StatusIndependant a
-> Either EsProtocolException (ParsedEsResponse a)
parseBHResponse BHResponse StatusIndependant a
r =
ParsedEsResponse a
-> Either EsProtocolException (ParsedEsResponse a)
forall a. a -> Either EsProtocolException a
forall (m :: * -> *) a. Monad m => a -> m a
return (ParsedEsResponse a
-> Either EsProtocolException (ParsedEsResponse a))
-> ParsedEsResponse a
-> Either EsProtocolException (ParsedEsResponse a)
forall a b. (a -> b) -> a -> b
$
case BHResponse StatusIndependant a -> Either String a
forall a.
FromJSON a =>
BHResponse StatusIndependant a -> Either String a
eitherDecodeResponse BHResponse StatusIndependant a
r of
Right a
d -> a -> ParsedEsResponse a
forall a b. b -> Either a b
Right a
d
Left String
e ->
EsError -> ParsedEsResponse a
forall a b. a -> Either a b
Left (EsError -> ParsedEsResponse a) -> EsError -> ParsedEsResponse a
forall a b. (a -> b) -> a -> b
$
EsError
{ errorStatus :: Maybe Int
errorStatus = Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int) -> Int -> Maybe Int
forall a b. (a -> b) -> a -> b
$ Status -> Int
NHTS.statusCode (Response ByteString -> Status
forall body. Response body -> Status
responseStatus (Response ByteString -> Status) -> Response ByteString -> Status
forall a b. (a -> b) -> a -> b
$ BHResponse StatusIndependant a -> Response ByteString
forall parsingContext body.
BHResponse parsingContext body -> Response ByteString
getResponse BHResponse StatusIndependant a
r),
errorMessage :: Text
errorMessage = Text
"Unable to parse body: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack String
e
}
withBHResponse ::
forall a parsingContext b.
(Either EsProtocolException (ParsedEsResponse a) -> BHResponse StatusDependant a -> b) ->
BHRequest parsingContext a ->
BHRequest StatusDependant b
withBHResponse :: forall a parsingContext b.
(Either EsProtocolException (ParsedEsResponse a)
-> BHResponse StatusDependant a -> b)
-> BHRequest parsingContext a -> BHRequest StatusDependant b
withBHResponse Either EsProtocolException (ParsedEsResponse a)
-> BHResponse StatusDependant a -> b
f BHRequest parsingContext a
req =
BHRequest parsingContext a
req
{ bhRequestParser = \BHResponse StatusDependant b
resp ->
b -> Either EsProtocolException (ParsedEsResponse b)
liftResponse (b -> Either EsProtocolException (ParsedEsResponse b))
-> b -> Either EsProtocolException (ParsedEsResponse b)
forall a b. (a -> b) -> a -> b
$ Either EsProtocolException (ParsedEsResponse a)
-> BHResponse StatusDependant a -> b
f (BHRequest parsingContext a
-> BHResponse parsingContext a
-> Either EsProtocolException (ParsedEsResponse a)
forall parsingContext responseBody.
BHRequest parsingContext responseBody
-> BHResponse parsingContext responseBody
-> Either EsProtocolException (ParsedEsResponse responseBody)
bhRequestParser BHRequest parsingContext a
req (BHResponse parsingContext a
-> Either EsProtocolException (ParsedEsResponse a))
-> BHResponse parsingContext a
-> Either EsProtocolException (ParsedEsResponse a)
forall a b. (a -> b) -> a -> b
$ forall parsingContext0 responseBody0 parsingContext1 responseBody1.
BHResponse parsingContext0 responseBody0
-> BHResponse parsingContext1 responseBody1
castResponse @_ @_ @parsingContext @a BHResponse StatusDependant b
resp) (BHResponse StatusDependant a -> b)
-> BHResponse StatusDependant a -> b
forall a b. (a -> b) -> a -> b
$ forall parsingContext0 responseBody0 parsingContext1 responseBody1.
BHResponse parsingContext0 responseBody0
-> BHResponse parsingContext1 responseBody1
castResponse @_ @_ @StatusDependant @a BHResponse StatusDependant b
resp
}
where
liftResponse :: b -> Either EsProtocolException (ParsedEsResponse b)
liftResponse :: b -> Either EsProtocolException (ParsedEsResponse b)
liftResponse = ParsedEsResponse b
-> Either EsProtocolException (ParsedEsResponse b)
forall a. a -> Either EsProtocolException a
forall (m :: * -> *) a. Monad m => a -> m a
return (ParsedEsResponse b
-> Either EsProtocolException (ParsedEsResponse b))
-> (b -> ParsedEsResponse b)
-> b
-> Either EsProtocolException (ParsedEsResponse b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> ParsedEsResponse b
forall a. a -> Either EsError a
forall (m :: * -> *) a. Monad m => a -> m a
return
castResponse :: BHResponse parsingContext0 responseBody0 -> BHResponse parsingContext1 responseBody1
castResponse :: forall parsingContext0 responseBody0 parsingContext1 responseBody1.
BHResponse parsingContext0 responseBody0
-> BHResponse parsingContext1 responseBody1
castResponse BHResponse {Response ByteString
getResponse :: forall parsingContext body.
BHResponse parsingContext body -> Response ByteString
getResponse :: Response ByteString
..} = BHResponse {Response ByteString
getResponse :: Response ByteString
getResponse :: Response ByteString
..}
withBHResponse_ ::
forall a parsingContext b.
(BHResponse StatusDependant a -> b) ->
BHRequest parsingContext a ->
BHRequest StatusDependant b
withBHResponse_ :: forall a parsingContext b.
(BHResponse StatusDependant a -> b)
-> BHRequest parsingContext a -> BHRequest StatusDependant b
withBHResponse_ BHResponse StatusDependant a -> b
f = (Either EsProtocolException (ParsedEsResponse a)
-> BHResponse StatusDependant a -> b)
-> BHRequest parsingContext a -> BHRequest StatusDependant b
forall a parsingContext b.
(Either EsProtocolException (ParsedEsResponse a)
-> BHResponse StatusDependant a -> b)
-> BHRequest parsingContext a -> BHRequest StatusDependant b
withBHResponse ((Either EsProtocolException (ParsedEsResponse a)
-> BHResponse StatusDependant a -> b)
-> BHRequest parsingContext a -> BHRequest StatusDependant b)
-> (Either EsProtocolException (ParsedEsResponse a)
-> BHResponse StatusDependant a -> b)
-> BHRequest parsingContext a
-> BHRequest StatusDependant b
forall a b. (a -> b) -> a -> b
$ (BHResponse StatusDependant a -> b)
-> Either EsProtocolException (ParsedEsResponse a)
-> BHResponse StatusDependant a
-> b
forall a b. a -> b -> a
const BHResponse StatusDependant a -> b
f
withBHResponseParsedEsResponse ::
forall a parsingContext.
BHRequest parsingContext a ->
BHRequest StatusDependant (ParsedEsResponse a)
withBHResponseParsedEsResponse :: forall a parsingContext.
BHRequest parsingContext a
-> BHRequest StatusDependant (ParsedEsResponse a)
withBHResponseParsedEsResponse BHRequest parsingContext a
req =
BHRequest parsingContext a
req
{ bhRequestParser = \BHResponse {Response ByteString
getResponse :: forall parsingContext body.
BHResponse parsingContext body -> Response ByteString
getResponse :: Response ByteString
..} -> ParsedEsResponse a -> ParsedEsResponse (ParsedEsResponse a)
forall a. a -> Either EsError a
forall (m :: * -> *) a. Monad m => a -> m a
return (ParsedEsResponse a -> ParsedEsResponse (ParsedEsResponse a))
-> Either EsProtocolException (ParsedEsResponse a)
-> Either
EsProtocolException (ParsedEsResponse (ParsedEsResponse a))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BHRequest parsingContext a
-> BHResponse parsingContext a
-> Either EsProtocolException (ParsedEsResponse a)
forall parsingContext responseBody.
BHRequest parsingContext responseBody
-> BHResponse parsingContext responseBody
-> Either EsProtocolException (ParsedEsResponse responseBody)
bhRequestParser BHRequest parsingContext a
req BHResponse {Response ByteString
getResponse :: Response ByteString
getResponse :: Response ByteString
..}
}
keepBHResponse ::
forall a parsingContext.
BHRequest parsingContext a ->
BHRequest StatusDependant (BHResponse StatusDependant a, a)
keepBHResponse :: forall a parsingContext.
BHRequest parsingContext a
-> BHRequest StatusDependant (BHResponse StatusDependant a, a)
keepBHResponse = BHRequest
StatusDependant
(Either
EsProtocolException
(ParsedEsResponse (BHResponse StatusDependant a, a)))
-> BHRequest StatusDependant (BHResponse StatusDependant a, a)
forall a parsingContext.
BHRequest
parsingContext (Either EsProtocolException (ParsedEsResponse a))
-> BHRequest parsingContext a
joinBHResponse (BHRequest
StatusDependant
(Either
EsProtocolException
(ParsedEsResponse (BHResponse StatusDependant a, a)))
-> BHRequest StatusDependant (BHResponse StatusDependant a, a))
-> (BHRequest parsingContext a
-> BHRequest
StatusDependant
(Either
EsProtocolException
(ParsedEsResponse (BHResponse StatusDependant a, a))))
-> BHRequest parsingContext a
-> BHRequest StatusDependant (BHResponse StatusDependant a, a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Either EsProtocolException (ParsedEsResponse a)
-> BHResponse StatusDependant a
-> Either
EsProtocolException
(ParsedEsResponse (BHResponse StatusDependant a, a)))
-> BHRequest parsingContext a
-> BHRequest
StatusDependant
(Either
EsProtocolException
(ParsedEsResponse (BHResponse StatusDependant a, a)))
forall a parsingContext b.
(Either EsProtocolException (ParsedEsResponse a)
-> BHResponse StatusDependant a -> b)
-> BHRequest parsingContext a -> BHRequest StatusDependant b
withBHResponse (\Either EsProtocolException (ParsedEsResponse a)
parsed BHResponse StatusDependant a
resp -> (ParsedEsResponse a
-> ParsedEsResponse (BHResponse StatusDependant a, a))
-> Either EsProtocolException (ParsedEsResponse a)
-> Either
EsProtocolException
(ParsedEsResponse (BHResponse StatusDependant a, a))
forall a b.
(a -> b)
-> Either EsProtocolException a -> Either EsProtocolException b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> (BHResponse StatusDependant a, a))
-> ParsedEsResponse a
-> ParsedEsResponse (BHResponse StatusDependant a, a)
forall a b. (a -> b) -> Either EsError a -> Either EsError b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((,) BHResponse StatusDependant a
resp)) Either EsProtocolException (ParsedEsResponse a)
parsed)
joinBHResponse ::
forall a parsingContext.
BHRequest parsingContext (Either EsProtocolException (ParsedEsResponse a)) ->
BHRequest parsingContext a
joinBHResponse :: forall a parsingContext.
BHRequest
parsingContext (Either EsProtocolException (ParsedEsResponse a))
-> BHRequest parsingContext a
joinBHResponse BHRequest
parsingContext (Either EsProtocolException (ParsedEsResponse a))
req =
BHRequest
parsingContext (Either EsProtocolException (ParsedEsResponse a))
req
{ bhRequestParser = \BHResponse parsingContext a
resp ->
case BHRequest
parsingContext (Either EsProtocolException (ParsedEsResponse a))
-> BHResponse
parsingContext (Either EsProtocolException (ParsedEsResponse a))
-> Either
EsProtocolException
(ParsedEsResponse
(Either EsProtocolException (ParsedEsResponse a)))
forall parsingContext responseBody.
BHRequest parsingContext responseBody
-> BHResponse parsingContext responseBody
-> Either EsProtocolException (ParsedEsResponse responseBody)
bhRequestParser BHRequest
parsingContext (Either EsProtocolException (ParsedEsResponse a))
req (BHResponse
parsingContext (Either EsProtocolException (ParsedEsResponse a))
-> Either
EsProtocolException
(ParsedEsResponse
(Either EsProtocolException (ParsedEsResponse a))))
-> BHResponse
parsingContext (Either EsProtocolException (ParsedEsResponse a))
-> Either
EsProtocolException
(ParsedEsResponse
(Either EsProtocolException (ParsedEsResponse a)))
forall a b. (a -> b) -> a -> b
$ BHResponse parsingContext a
-> BHResponse
parsingContext (Either EsProtocolException (ParsedEsResponse a))
forall parsingContext0 responseBody0 parsingContext1 responseBody1.
BHResponse parsingContext0 responseBody0
-> BHResponse parsingContext1 responseBody1
castResponse BHResponse parsingContext a
resp of
Left EsProtocolException
e -> EsProtocolException
-> Either EsProtocolException (ParsedEsResponse a)
forall a b. a -> Either a b
Left EsProtocolException
e
Right (Right Either EsProtocolException (ParsedEsResponse a)
a) -> Either EsProtocolException (ParsedEsResponse a)
a
Right (Left EsError
e) -> ParsedEsResponse a
-> Either EsProtocolException (ParsedEsResponse a)
forall a b. b -> Either a b
Right (EsError -> ParsedEsResponse a
forall a b. a -> Either a b
Left EsError
e)
}
newtype BHResponse parsingContext body = BHResponse
{ forall parsingContext body.
BHResponse parsingContext body -> Response ByteString
getResponse :: Network.HTTP.Client.Response BL.ByteString
}
deriving stock (Int -> BHResponse parsingContext body -> ShowS
[BHResponse parsingContext body] -> ShowS
BHResponse parsingContext body -> String
(Int -> BHResponse parsingContext body -> ShowS)
-> (BHResponse parsingContext body -> String)
-> ([BHResponse parsingContext body] -> ShowS)
-> Show (BHResponse parsingContext body)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall parsingContext body.
Int -> BHResponse parsingContext body -> ShowS
forall parsingContext body.
[BHResponse parsingContext body] -> ShowS
forall parsingContext body.
BHResponse parsingContext body -> String
$cshowsPrec :: forall parsingContext body.
Int -> BHResponse parsingContext body -> ShowS
showsPrec :: Int -> BHResponse parsingContext body -> ShowS
$cshow :: forall parsingContext body.
BHResponse parsingContext body -> String
show :: BHResponse parsingContext body -> String
$cshowList :: forall parsingContext body.
[BHResponse parsingContext body] -> ShowS
showList :: [BHResponse parsingContext body] -> ShowS
Show)
type ParsedEsResponse a = Either EsError a
parseEsResponse ::
(FromJSON body) =>
BHResponse parsingContext body ->
Either EsProtocolException (ParsedEsResponse body)
parseEsResponse :: forall body parsingContext.
FromJSON body =>
BHResponse parsingContext body
-> Either EsProtocolException (ParsedEsResponse body)
parseEsResponse BHResponse parsingContext body
response
| BHResponse parsingContext body -> Bool
forall parsingContext a. BHResponse parsingContext a -> Bool
isSuccess BHResponse parsingContext body
response = case ByteString -> Either String body
forall a. FromJSON a => ByteString -> Either String a
eitherDecode ByteString
body of
Right body
a -> ParsedEsResponse body
-> Either EsProtocolException (ParsedEsResponse body)
forall a. a -> Either EsProtocolException a
forall (m :: * -> *) a. Monad m => a -> m a
return (body -> ParsedEsResponse body
forall a b. b -> Either a b
Right body
a)
Left String
err ->
String -> Either EsProtocolException (ParsedEsResponse body)
tryParseError String
err
| Bool
otherwise = String -> Either EsProtocolException (ParsedEsResponse body)
tryParseError String
"Non-200 status code"
where
body :: ByteString
body = Response ByteString -> ByteString
forall body. Response body -> body
responseBody (Response ByteString -> ByteString)
-> Response ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ BHResponse parsingContext body -> Response ByteString
forall parsingContext body.
BHResponse parsingContext body -> Response ByteString
getResponse BHResponse parsingContext body
response
tryParseError :: String -> Either EsProtocolException (ParsedEsResponse body)
tryParseError String
originalError =
case ByteString -> Either String EsError
forall a. FromJSON a => ByteString -> Either String a
eitherDecode ByteString
body of
Right EsError
e -> ParsedEsResponse body
-> Either EsProtocolException (ParsedEsResponse body)
forall a. a -> Either EsProtocolException a
forall (m :: * -> *) a. Monad m => a -> m a
return (EsError -> ParsedEsResponse body
forall a b. a -> Either a b
Left EsError
e)
Left String
err -> String -> Either EsProtocolException (ParsedEsResponse body)
explode (String
"Original error was: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
originalError String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" Error parse failure was: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
err)
explode :: String -> Either EsProtocolException (ParsedEsResponse body)
explode String
errorMsg = EsProtocolException
-> Either EsProtocolException (ParsedEsResponse body)
forall a b. a -> Either a b
Left (EsProtocolException
-> Either EsProtocolException (ParsedEsResponse body))
-> EsProtocolException
-> Either EsProtocolException (ParsedEsResponse body)
forall a b. (a -> b) -> a -> b
$ Text -> ByteString -> EsProtocolException
EsProtocolException (String -> Text
T.pack String
errorMsg) ByteString
body
parseEsResponseWith ::
( MonadThrow m,
FromJSON body
) =>
(body -> Either String parsed) ->
BHResponse parsingContext body ->
m parsed
parseEsResponseWith :: forall (m :: * -> *) body parsed parsingContext.
(MonadThrow m, FromJSON body) =>
(body -> Either String parsed)
-> BHResponse parsingContext body -> m parsed
parseEsResponseWith body -> Either String parsed
parser BHResponse parsingContext body
response =
case ByteString -> Either String body
forall a. FromJSON a => ByteString -> Either String a
eitherDecode ByteString
body of
Left String
e -> String -> m parsed
explode String
e
Right body
parsed ->
case body -> Either String parsed
parser body
parsed of
Right parsed
a -> parsed -> m parsed
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return parsed
a
Left String
e -> String -> m parsed
explode String
e
where
body :: ByteString
body = Response ByteString -> ByteString
forall body. Response body -> body
responseBody (Response ByteString -> ByteString)
-> Response ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ BHResponse parsingContext body -> Response ByteString
forall parsingContext body.
BHResponse parsingContext body -> Response ByteString
getResponse BHResponse parsingContext body
response
explode :: String -> m parsed
explode String
errorMsg = EsProtocolException -> m parsed
forall e a. (HasCallStack, Exception e) => e -> m a
forall (m :: * -> *) e a.
(MonadThrow m, HasCallStack, Exception e) =>
e -> m a
throwM (EsProtocolException -> m parsed)
-> EsProtocolException -> m parsed
forall a b. (a -> b) -> a -> b
$ Text -> ByteString -> EsProtocolException
EsProtocolException (String -> Text
T.pack String
errorMsg) ByteString
body
decodeResponse ::
(FromJSON a) =>
BHResponse StatusIndependant a ->
Maybe a
decodeResponse :: forall a. FromJSON a => BHResponse StatusIndependant a -> Maybe a
decodeResponse = ByteString -> Maybe a
forall a. FromJSON a => ByteString -> Maybe a
decode (ByteString -> Maybe a)
-> (BHResponse StatusIndependant a -> ByteString)
-> BHResponse StatusIndependant a
-> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Response ByteString -> ByteString
forall body. Response body -> body
responseBody (Response ByteString -> ByteString)
-> (BHResponse StatusIndependant a -> Response ByteString)
-> BHResponse StatusIndependant a
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BHResponse StatusIndependant a -> Response ByteString
forall parsingContext body.
BHResponse parsingContext body -> Response ByteString
getResponse
eitherDecodeResponse ::
(FromJSON a) =>
BHResponse StatusIndependant a ->
Either String a
eitherDecodeResponse :: forall a.
FromJSON a =>
BHResponse StatusIndependant a -> Either String a
eitherDecodeResponse = ByteString -> Either String a
forall a. FromJSON a => ByteString -> Either String a
eitherDecode (ByteString -> Either String a)
-> (BHResponse StatusIndependant a -> ByteString)
-> BHResponse StatusIndependant a
-> Either String a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Response ByteString -> ByteString
forall body. Response body -> body
responseBody (Response ByteString -> ByteString)
-> (BHResponse StatusIndependant a -> Response ByteString)
-> BHResponse StatusIndependant a
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BHResponse StatusIndependant a -> Response ByteString
forall parsingContext body.
BHResponse parsingContext body -> Response ByteString
getResponse
isVersionConflict :: BHResponse parsingContext a -> Bool
isVersionConflict :: forall parsingContext a. BHResponse parsingContext a -> Bool
isVersionConflict = (Int -> Bool) -> BHResponse parsingContext a -> Bool
forall parsingContext a.
(Int -> Bool) -> BHResponse parsingContext a -> Bool
statusCheck (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
409)
isSuccess :: BHResponse parsingContext a -> Bool
isSuccess :: forall parsingContext a. BHResponse parsingContext a -> Bool
isSuccess = (Int, Int) -> BHResponse parsingContext a -> Bool
forall parsingContext body.
(Int, Int) -> BHResponse parsingContext body -> Bool
statusCodeIs (Int
200, Int
299)
isCreated :: BHResponse parsingContext a -> Bool
isCreated :: forall parsingContext a. BHResponse parsingContext a -> Bool
isCreated = (Int -> Bool) -> BHResponse parsingContext a -> Bool
forall parsingContext a.
(Int -> Bool) -> BHResponse parsingContext a -> Bool
statusCheck (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
201)
statusCheck :: (Int -> Bool) -> BHResponse parsingContext a -> Bool
statusCheck :: forall parsingContext a.
(Int -> Bool) -> BHResponse parsingContext a -> Bool
statusCheck Int -> Bool
prd = Int -> Bool
prd (Int -> Bool)
-> (BHResponse parsingContext a -> Int)
-> BHResponse parsingContext a
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Status -> Int
NHTS.statusCode (Status -> Int)
-> (BHResponse parsingContext a -> Status)
-> BHResponse parsingContext a
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Response ByteString -> Status
forall body. Response body -> Status
responseStatus (Response ByteString -> Status)
-> (BHResponse parsingContext a -> Response ByteString)
-> BHResponse parsingContext a
-> Status
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BHResponse parsingContext a -> Response ByteString
forall parsingContext body.
BHResponse parsingContext body -> Response ByteString
getResponse
statusCodeIs :: (Int, Int) -> BHResponse parsingContext body -> Bool
statusCodeIs :: forall parsingContext body.
(Int, Int) -> BHResponse parsingContext body -> Bool
statusCodeIs (Int, Int)
r BHResponse parsingContext body
resp = (Int, Int) -> Int -> Bool
forall a. Ix a => (a, a) -> a -> Bool
inRange (Int, Int)
r (Int -> Bool) -> Int -> Bool
forall a b. (a -> b) -> a -> b
$ Status -> Int
NHTS.statusCode (Response ByteString -> Status
forall body. Response body -> Status
responseStatus (Response ByteString -> Status) -> Response ByteString -> Status
forall a b. (a -> b) -> a -> b
$ BHResponse parsingContext body -> Response ByteString
forall parsingContext body.
BHResponse parsingContext body -> Response ByteString
getResponse BHResponse parsingContext body
resp)
data EsResult a = EsResult
{ forall a. EsResult a -> Text
_index :: Text,
forall a. EsResult a -> Maybe Text
_type :: Maybe Text,
forall a. EsResult a -> Text
_id :: Text,
forall a. EsResult a -> Maybe (EsResultFound a)
foundResult :: Maybe (EsResultFound a)
}
deriving stock (EsResult a -> EsResult a -> Bool
(EsResult a -> EsResult a -> Bool)
-> (EsResult a -> EsResult a -> Bool) -> Eq (EsResult a)
forall a. Eq a => EsResult a -> EsResult a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => EsResult a -> EsResult a -> Bool
== :: EsResult a -> EsResult a -> Bool
$c/= :: forall a. Eq a => EsResult a -> EsResult a -> Bool
/= :: EsResult a -> EsResult a -> Bool
Eq, Int -> EsResult a -> ShowS
[EsResult a] -> ShowS
EsResult a -> String
(Int -> EsResult a -> ShowS)
-> (EsResult a -> String)
-> ([EsResult a] -> ShowS)
-> Show (EsResult a)
forall a. Show a => Int -> EsResult a -> ShowS
forall a. Show a => [EsResult a] -> ShowS
forall a. Show a => EsResult a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> EsResult a -> ShowS
showsPrec :: Int -> EsResult a -> ShowS
$cshow :: forall a. Show a => EsResult a -> String
show :: EsResult a -> String
$cshowList :: forall a. Show a => [EsResult a] -> ShowS
showList :: [EsResult a] -> ShowS
Show)
{-# DEPRECATED _type "deprecated since ElasticSearch 6.0" #-}
data EsResultFound a = EsResultFound
{ forall a. EsResultFound a -> DocVersion
_version :: DocVersion,
forall a. EsResultFound a -> a
_source :: a
}
deriving stock (EsResultFound a -> EsResultFound a -> Bool
(EsResultFound a -> EsResultFound a -> Bool)
-> (EsResultFound a -> EsResultFound a -> Bool)
-> Eq (EsResultFound a)
forall a. Eq a => EsResultFound a -> EsResultFound a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => EsResultFound a -> EsResultFound a -> Bool
== :: EsResultFound a -> EsResultFound a -> Bool
$c/= :: forall a. Eq a => EsResultFound a -> EsResultFound a -> Bool
/= :: EsResultFound a -> EsResultFound a -> Bool
Eq, Int -> EsResultFound a -> ShowS
[EsResultFound a] -> ShowS
EsResultFound a -> String
(Int -> EsResultFound a -> ShowS)
-> (EsResultFound a -> String)
-> ([EsResultFound a] -> ShowS)
-> Show (EsResultFound a)
forall a. Show a => Int -> EsResultFound a -> ShowS
forall a. Show a => [EsResultFound a] -> ShowS
forall a. Show a => EsResultFound a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> EsResultFound a -> ShowS
showsPrec :: Int -> EsResultFound a -> ShowS
$cshow :: forall a. Show a => EsResultFound a -> String
show :: EsResultFound a -> String
$cshowList :: forall a. Show a => [EsResultFound a] -> ShowS
showList :: [EsResultFound a] -> ShowS
Show)
instance (FromJSON a) => FromJSON (EsResult a) where
parseJSON :: Value -> Parser (EsResult a)
parseJSON jsonVal :: Value
jsonVal@(Object Object
v) = do
Bool
found <- Object
v Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"found" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
Maybe (EsResultFound a)
fr <-
if Bool
found
then Value -> Parser (Maybe (EsResultFound a))
forall a. FromJSON a => Value -> Parser a
parseJSON Value
jsonVal
else Maybe (EsResultFound a) -> Parser (Maybe (EsResultFound a))
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (EsResultFound a)
forall a. Maybe a
Nothing
Text -> Maybe Text -> Text -> Maybe (EsResultFound a) -> EsResult a
forall a.
Text -> Maybe Text -> Text -> Maybe (EsResultFound a) -> EsResult a
EsResult
(Text
-> Maybe Text -> Text -> Maybe (EsResultFound a) -> EsResult a)
-> Parser Text
-> Parser
(Maybe Text -> Text -> Maybe (EsResultFound a) -> EsResult a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v
Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"_index"
Parser
(Maybe Text -> Text -> Maybe (EsResultFound a) -> EsResult a)
-> Parser (Maybe Text)
-> Parser (Text -> Maybe (EsResultFound a) -> EsResult a)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v
Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"_type"
Parser (Text -> Maybe (EsResultFound a) -> EsResult a)
-> Parser Text -> Parser (Maybe (EsResultFound a) -> EsResult a)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v
Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"_id"
Parser (Maybe (EsResultFound a) -> EsResult a)
-> Parser (Maybe (EsResultFound a)) -> Parser (EsResult a)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe (EsResultFound a) -> Parser (Maybe (EsResultFound a))
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (EsResultFound a)
fr
parseJSON Value
_ = Parser (EsResult a)
forall a. Parser a
forall (f :: * -> *) a. Alternative f => f a
empty
instance (FromJSON a) => FromJSON (EsResultFound a) where
parseJSON :: Value -> Parser (EsResultFound a)
parseJSON (Object Object
v) =
DocVersion -> a -> EsResultFound a
forall a. DocVersion -> a -> EsResultFound a
EsResultFound
(DocVersion -> a -> EsResultFound a)
-> Parser DocVersion -> Parser (a -> EsResultFound a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v
Object -> Key -> Parser DocVersion
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"_version"
Parser (a -> EsResultFound a)
-> Parser a -> Parser (EsResultFound a)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v
Object -> Key -> Parser a
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"_source"
parseJSON Value
_ = Parser (EsResultFound a)
forall a. Parser a
forall (f :: * -> *) a. Alternative f => f a
empty
data EsError = EsError
{ EsError -> Maybe Int
errorStatus :: Maybe Int,
EsError -> Text
errorMessage :: Text
}
deriving stock (EsError -> EsError -> Bool
(EsError -> EsError -> Bool)
-> (EsError -> EsError -> Bool) -> Eq EsError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EsError -> EsError -> Bool
== :: EsError -> EsError -> Bool
$c/= :: EsError -> EsError -> Bool
/= :: EsError -> EsError -> Bool
Eq, Int -> EsError -> ShowS
[EsError] -> ShowS
EsError -> String
(Int -> EsError -> ShowS)
-> (EsError -> String) -> ([EsError] -> ShowS) -> Show EsError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EsError -> ShowS
showsPrec :: Int -> EsError -> ShowS
$cshow :: EsError -> String
show :: EsError -> String
$cshowList :: [EsError] -> ShowS
showList :: [EsError] -> ShowS
Show, Typeable)
{-# DEPRECATED errorStatus "deprecated since ElasticSearch 6.0" #-}
instance Exception EsError
instance Semigroup EsError where
EsError
_ <> :: EsError -> EsError -> EsError
<> EsError
x = EsError
x
instance Monoid EsError where
mempty :: EsError
mempty = Maybe Int -> Text -> EsError
EsError Maybe Int
forall a. Maybe a
Nothing Text
"Monoid value, shouldn't happen"
instance FromJSON EsError where
parseJSON :: Value -> Parser EsError
parseJSON (Object Object
v) = Parser EsError
p1 Parser EsError -> Parser EsError -> Parser EsError
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser EsError
p2 Parser EsError -> Parser EsError -> Parser EsError
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser EsError
p3
where
p1 :: Parser EsError
p1 =
Maybe Int -> Text -> EsError
EsError
(Maybe Int -> Text -> EsError)
-> Parser (Maybe Int) -> Parser (Text -> EsError)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"status"
Parser (Text -> EsError) -> Parser Text -> Parser EsError
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"error"
p2 :: Parser EsError
p2 =
Maybe Int -> Text -> EsError
EsError
(Maybe Int -> Text -> EsError)
-> Parser (Maybe Int) -> Parser (Text -> EsError)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"status"
Parser (Text -> EsError) -> Parser Text -> Parser EsError
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
v Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"error" Parser Object -> (Object -> Parser Text) -> Parser Text
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"reason"))
p3 :: Parser EsError
p3 = do
[Object]
failures <- Object
v Object -> Key -> Parser [Object]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"failures"
case [Object]
failures of
(Object
failure : [Object]
_) ->
Maybe Int -> Text -> EsError
EsError
(Maybe Int -> Text -> EsError)
-> Parser (Maybe Int) -> Parser (Text -> EsError)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
failure Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"status"
Parser (Text -> EsError) -> Parser Text -> Parser EsError
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
failure Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"cause" Parser Object -> (Object -> Parser Text) -> Parser Text
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"reason"))
[] -> String -> Parser EsError
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"could not find field `failure`"
parseJSON Value
_ = Parser EsError
forall a. Parser a
forall (f :: * -> *) a. Alternative f => f a
empty
data EsProtocolException = EsProtocolException
{ EsProtocolException -> Text
esProtoExMessage :: !Text,
EsProtocolException -> ByteString
esProtoExResponse :: !BL.ByteString
}
deriving stock (EsProtocolException -> EsProtocolException -> Bool
(EsProtocolException -> EsProtocolException -> Bool)
-> (EsProtocolException -> EsProtocolException -> Bool)
-> Eq EsProtocolException
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EsProtocolException -> EsProtocolException -> Bool
== :: EsProtocolException -> EsProtocolException -> Bool
$c/= :: EsProtocolException -> EsProtocolException -> Bool
/= :: EsProtocolException -> EsProtocolException -> Bool
Eq, Int -> EsProtocolException -> ShowS
[EsProtocolException] -> ShowS
EsProtocolException -> String
(Int -> EsProtocolException -> ShowS)
-> (EsProtocolException -> String)
-> ([EsProtocolException] -> ShowS)
-> Show EsProtocolException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EsProtocolException -> ShowS
showsPrec :: Int -> EsProtocolException -> ShowS
$cshow :: EsProtocolException -> String
show :: EsProtocolException -> String
$cshowList :: [EsProtocolException] -> ShowS
showList :: [EsProtocolException] -> ShowS
Show)
instance Exception EsProtocolException
newtype Acknowledged = Acknowledged {Acknowledged -> Bool
isAcknowledged :: Bool}
deriving stock (Acknowledged -> Acknowledged -> Bool
(Acknowledged -> Acknowledged -> Bool)
-> (Acknowledged -> Acknowledged -> Bool) -> Eq Acknowledged
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Acknowledged -> Acknowledged -> Bool
== :: Acknowledged -> Acknowledged -> Bool
$c/= :: Acknowledged -> Acknowledged -> Bool
/= :: Acknowledged -> Acknowledged -> Bool
Eq, Int -> Acknowledged -> ShowS
[Acknowledged] -> ShowS
Acknowledged -> String
(Int -> Acknowledged -> ShowS)
-> (Acknowledged -> String)
-> ([Acknowledged] -> ShowS)
-> Show Acknowledged
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Acknowledged -> ShowS
showsPrec :: Int -> Acknowledged -> ShowS
$cshow :: Acknowledged -> String
show :: Acknowledged -> String
$cshowList :: [Acknowledged] -> ShowS
showList :: [Acknowledged] -> ShowS
Show)
instance FromJSON Acknowledged where
parseJSON :: Value -> Parser Acknowledged
parseJSON =
String
-> (Object -> Parser Acknowledged) -> Value -> Parser Acknowledged
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Acknowledged" ((Object -> Parser Acknowledged) -> Value -> Parser Acknowledged)
-> (Object -> Parser Acknowledged) -> Value -> Parser Acknowledged
forall a b. (a -> b) -> a -> b
$
(Bool -> Acknowledged) -> Parser Bool -> Parser Acknowledged
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Bool -> Acknowledged
Acknowledged (Parser Bool -> Parser Acknowledged)
-> (Object -> Parser Bool) -> Object -> Parser Acknowledged
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Object -> Key -> Parser Bool
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"acknowledged")
newtype Accepted = Accepted {Accepted -> Bool
isAccepted :: Bool}
deriving stock (Accepted -> Accepted -> Bool
(Accepted -> Accepted -> Bool)
-> (Accepted -> Accepted -> Bool) -> Eq Accepted
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Accepted -> Accepted -> Bool
== :: Accepted -> Accepted -> Bool
$c/= :: Accepted -> Accepted -> Bool
/= :: Accepted -> Accepted -> Bool
Eq, Int -> Accepted -> ShowS
[Accepted] -> ShowS
Accepted -> String
(Int -> Accepted -> ShowS)
-> (Accepted -> String) -> ([Accepted] -> ShowS) -> Show Accepted
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Accepted -> ShowS
showsPrec :: Int -> Accepted -> ShowS
$cshow :: Accepted -> String
show :: Accepted -> String
$cshowList :: [Accepted] -> ShowS
showList :: [Accepted] -> ShowS
Show)
instance FromJSON Accepted where
parseJSON :: Value -> Parser Accepted
parseJSON =
String -> (Object -> Parser Accepted) -> Value -> Parser Accepted
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Accepted" ((Object -> Parser Accepted) -> Value -> Parser Accepted)
-> (Object -> Parser Accepted) -> Value -> Parser Accepted
forall a b. (a -> b) -> a -> b
$
(Bool -> Accepted) -> Parser Bool -> Parser Accepted
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Bool -> Accepted
Accepted (Parser Bool -> Parser Accepted)
-> (Object -> Parser Bool) -> Object -> Parser Accepted
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Object -> Key -> Parser Bool
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"accepted")
data IgnoredBody = IgnoredBody
deriving stock (IgnoredBody -> IgnoredBody -> Bool
(IgnoredBody -> IgnoredBody -> Bool)
-> (IgnoredBody -> IgnoredBody -> Bool) -> Eq IgnoredBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IgnoredBody -> IgnoredBody -> Bool
== :: IgnoredBody -> IgnoredBody -> Bool
$c/= :: IgnoredBody -> IgnoredBody -> Bool
/= :: IgnoredBody -> IgnoredBody -> Bool
Eq, Int -> IgnoredBody -> ShowS
[IgnoredBody] -> ShowS
IgnoredBody -> String
(Int -> IgnoredBody -> ShowS)
-> (IgnoredBody -> String)
-> ([IgnoredBody] -> ShowS)
-> Show IgnoredBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IgnoredBody -> ShowS
showsPrec :: Int -> IgnoredBody -> ShowS
$cshow :: IgnoredBody -> String
show :: IgnoredBody -> String
$cshowList :: [IgnoredBody] -> ShowS
showList :: [IgnoredBody] -> ShowS
Show)
instance FromJSON IgnoredBody where
parseJSON :: Value -> Parser IgnoredBody
parseJSON Value
_ = IgnoredBody -> Parser IgnoredBody
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return IgnoredBody
IgnoredBody