{-# LANGUAGE DeriveDataTypeable #-}
module Database.Memcache.Errors (
        
        MemcacheError(..),
        Status(..),
        ClientError(..),
        ProtocolError(..),
        
        throwStatus,
        wrongOp
    ) where
import Database.Memcache.Types
import Control.Exception
import Data.Typeable
data MemcacheError
    
    = OpError Status
    
    | ClientError ClientError
    
    | ProtocolError ProtocolError
    deriving (MemcacheError -> MemcacheError -> Bool
(MemcacheError -> MemcacheError -> Bool)
-> (MemcacheError -> MemcacheError -> Bool) -> Eq MemcacheError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MemcacheError -> MemcacheError -> Bool
== :: MemcacheError -> MemcacheError -> Bool
$c/= :: MemcacheError -> MemcacheError -> Bool
/= :: MemcacheError -> MemcacheError -> Bool
Eq, Int -> MemcacheError -> ShowS
[MemcacheError] -> ShowS
MemcacheError -> String
(Int -> MemcacheError -> ShowS)
-> (MemcacheError -> String)
-> ([MemcacheError] -> ShowS)
-> Show MemcacheError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MemcacheError -> ShowS
showsPrec :: Int -> MemcacheError -> ShowS
$cshow :: MemcacheError -> String
show :: MemcacheError -> String
$cshowList :: [MemcacheError] -> ShowS
showList :: [MemcacheError] -> ShowS
Show, Typeable)
instance Exception MemcacheError
data ClientError
    
    = NoServersReady
    
    | Timeout
    deriving (ClientError -> ClientError -> Bool
(ClientError -> ClientError -> Bool)
-> (ClientError -> ClientError -> Bool) -> Eq ClientError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ClientError -> ClientError -> Bool
== :: ClientError -> ClientError -> Bool
$c/= :: ClientError -> ClientError -> Bool
/= :: ClientError -> ClientError -> Bool
Eq, Int -> ClientError -> ShowS
[ClientError] -> ShowS
ClientError -> String
(Int -> ClientError -> ShowS)
-> (ClientError -> String)
-> ([ClientError] -> ShowS)
-> Show ClientError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ClientError -> ShowS
showsPrec :: Int -> ClientError -> ShowS
$cshow :: ClientError -> String
show :: ClientError -> String
$cshowList :: [ClientError] -> ShowS
showList :: [ClientError] -> ShowS
Show, Typeable)
data ProtocolError
    
    = UnknownPkt    { ProtocolError -> String
protocolError :: String }
    
    | UnknownOp     { protocolError :: String }
    
    | UnknownStatus { protocolError :: String }
    
    | BadLength     { protocolError :: String }
    
    | WrongOp       { protocolError :: String }
    
    | UnexpectedEOF { protocolError :: String }
    deriving (ProtocolError -> ProtocolError -> Bool
(ProtocolError -> ProtocolError -> Bool)
-> (ProtocolError -> ProtocolError -> Bool) -> Eq ProtocolError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProtocolError -> ProtocolError -> Bool
== :: ProtocolError -> ProtocolError -> Bool
$c/= :: ProtocolError -> ProtocolError -> Bool
/= :: ProtocolError -> ProtocolError -> Bool
Eq, Int -> ProtocolError -> ShowS
[ProtocolError] -> ShowS
ProtocolError -> String
(Int -> ProtocolError -> ShowS)
-> (ProtocolError -> String)
-> ([ProtocolError] -> ShowS)
-> Show ProtocolError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ProtocolError -> ShowS
showsPrec :: Int -> ProtocolError -> ShowS
$cshow :: ProtocolError -> String
show :: ProtocolError -> String
$cshowList :: [ProtocolError] -> ShowS
showList :: [ProtocolError] -> ShowS
Show, Typeable)
throwStatus :: Status -> IO a
throwStatus :: forall a. Status -> IO a
throwStatus Status
s = MemcacheError -> IO a
forall e a. Exception e => e -> IO a
throwIO (MemcacheError -> IO a) -> MemcacheError -> IO a
forall a b. (a -> b) -> a -> b
$ Status -> MemcacheError
OpError Status
s
wrongOp :: Response -> String -> MemcacheError
wrongOp :: Response -> String -> MemcacheError
wrongOp Response
r String
msg = ProtocolError -> MemcacheError
ProtocolError (ProtocolError -> MemcacheError) -> ProtocolError -> MemcacheError
forall a b. (a -> b) -> a -> b
$
    WrongOp {
        protocolError :: String
protocolError  = String
"Expected " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
msg String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"! Got: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ OpResponse -> String
forall a. Show a => a -> String
show (Response -> OpResponse
resOp Response
r)
    }