{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
module Network.Livy.Types
(
LivyRequest (..)
, LivyResponse
, ToPath (..)
, ToQuery (..)
, LivyError (..)
, LivyErrorType (..)
, LivyHTTPErrorCode (..)
, leCode
, leMessage
, leResponseBody
, leType
) where
import Control.Exception
import Control.Lens
import qualified Data.ByteString as S
import qualified Data.ByteString.Lazy as LBS
import Data.Text (Text)
import qualified Data.Text.Encoding as T
import Data.Typeable
import Network.HTTP.Client
import Network.HTTP.Types
class ToPath a where
toPath :: a -> S.ByteString
instance ToPath Text where toPath = T.encodeUtf8
instance ToPath a => ToPath [a] where toPath = S.intercalate "/" . fmap toPath
class ToQuery a where
toQueryString :: a -> Query
class LivyRequest a where
request :: a -> Request
type family LivyResponse a :: *
data LivyErrorType
= InvalidRequest
| ParseFailure
| LibraryException HttpException
| UnknownErrorType
deriving (Show, Typeable)
data LivyHTTPErrorCode
= BadRequest
| Unauthorized
| RequestFailed
| Forbidden
| BadMethod
| NotFound
| ServerError
| UnknownHTTPErrorCode
deriving (Show, Typeable)
data LivyError = LivyError
{ _leType :: !LivyErrorType
, _leMessage :: !S.ByteString
, _leResponseBody :: !(Maybe LBS.ByteString)
, _leCode :: !(Maybe LivyHTTPErrorCode)
} deriving (Show, Typeable)
makeLenses ''LivyError
instance Exception LivyError where