-- |
-- An API for retrieval of multiple results.
-- Can be used to handle:
-- 
-- * A single result,
-- 
-- * Individual results of a multi-statement query
-- with the help of "Applicative" and "Monad",
-- 
-- * Row-by-row fetching.
-- 
module Hasql.Private.Errors where

import Hasql.Private.Prelude


-- |
-- An error during the execution of a query.
-- Comes packed with the query template and a textual representation of the provided params.
data QueryError =
  QueryError ByteString [Text] CommandError
  deriving (Int -> QueryError -> ShowS
[QueryError] -> ShowS
QueryError -> String
(Int -> QueryError -> ShowS)
-> (QueryError -> String)
-> ([QueryError] -> ShowS)
-> Show QueryError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QueryError] -> ShowS
$cshowList :: [QueryError] -> ShowS
show :: QueryError -> String
$cshow :: QueryError -> String
showsPrec :: Int -> QueryError -> ShowS
$cshowsPrec :: Int -> QueryError -> ShowS
Show, QueryError -> QueryError -> Bool
(QueryError -> QueryError -> Bool)
-> (QueryError -> QueryError -> Bool) -> Eq QueryError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QueryError -> QueryError -> Bool
$c/= :: QueryError -> QueryError -> Bool
== :: QueryError -> QueryError -> Bool
$c== :: QueryError -> QueryError -> Bool
Eq, Typeable)

instance Exception QueryError

-- |
-- An error of some command in the session.
data CommandError =
  -- |
  -- An error on the client-side,
  -- with a message generated by the \"libpq\" library.
  -- Usually indicates problems with connection.
  ClientError (Maybe ByteString) |
  -- |
  -- Some error with a command result.
  ResultError ResultError
  deriving (Int -> CommandError -> ShowS
[CommandError] -> ShowS
CommandError -> String
(Int -> CommandError -> ShowS)
-> (CommandError -> String)
-> ([CommandError] -> ShowS)
-> Show CommandError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommandError] -> ShowS
$cshowList :: [CommandError] -> ShowS
show :: CommandError -> String
$cshow :: CommandError -> String
showsPrec :: Int -> CommandError -> ShowS
$cshowsPrec :: Int -> CommandError -> ShowS
Show, CommandError -> CommandError -> Bool
(CommandError -> CommandError -> Bool)
-> (CommandError -> CommandError -> Bool) -> Eq CommandError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandError -> CommandError -> Bool
$c/= :: CommandError -> CommandError -> Bool
== :: CommandError -> CommandError -> Bool
$c== :: CommandError -> CommandError -> Bool
Eq)

-- |
-- An error with a command result.
data ResultError =
  -- | 
  -- An error reported by the DB.
  -- Consists of the following: Code, message, details, hint.
  -- 
  -- * __Code__.
  -- The SQLSTATE code for the error.
  -- It's recommended to use
  -- <http://hackage.haskell.org/package/postgresql-error-codes the "postgresql-error-codes" package>
  -- to work with those.
  -- 
  -- * __Message__.
  -- The primary human-readable error message (typically one line). Always present.
  -- 
  -- * __Details__.
  -- An optional secondary error message carrying more detail about the problem. 
  -- Might run to multiple lines.
  -- 
  -- * __Hint__.
  -- An optional suggestion on what to do about the problem. 
  -- This is intended to differ from detail in that it offers advice (potentially inappropriate) 
  -- rather than hard facts.
  -- Might run to multiple lines.
  ServerError ByteString ByteString (Maybe ByteString) (Maybe ByteString) |
  -- |
  -- The database returned an unexpected result.
  -- Indicates an improper statement or a schema mismatch.
  UnexpectedResult Text |
  -- |
  -- An error of the row reader, preceded by the index of the row.
  RowError Int RowError |
  -- |
  -- An unexpected amount of rows.
  UnexpectedAmountOfRows Int
  deriving (Int -> ResultError -> ShowS
[ResultError] -> ShowS
ResultError -> String
(Int -> ResultError -> ShowS)
-> (ResultError -> String)
-> ([ResultError] -> ShowS)
-> Show ResultError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResultError] -> ShowS
$cshowList :: [ResultError] -> ShowS
show :: ResultError -> String
$cshow :: ResultError -> String
showsPrec :: Int -> ResultError -> ShowS
$cshowsPrec :: Int -> ResultError -> ShowS
Show, ResultError -> ResultError -> Bool
(ResultError -> ResultError -> Bool)
-> (ResultError -> ResultError -> Bool) -> Eq ResultError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResultError -> ResultError -> Bool
$c/= :: ResultError -> ResultError -> Bool
== :: ResultError -> ResultError -> Bool
$c== :: ResultError -> ResultError -> Bool
Eq)

-- |
-- An error during the decoding of a specific row.
data RowError =
  -- |
  -- Appears on the attempt to parse more columns than there are in the result.
  EndOfInput |
  -- |
  -- Appears on the attempt to parse a @NULL@ as some value.
  UnexpectedNull |
  -- |
  -- Appears when a wrong value parser is used.
  -- Comes with the error details.
  ValueError Text
  deriving (Int -> RowError -> ShowS
[RowError] -> ShowS
RowError -> String
(Int -> RowError -> ShowS)
-> (RowError -> String) -> ([RowError] -> ShowS) -> Show RowError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RowError] -> ShowS
$cshowList :: [RowError] -> ShowS
show :: RowError -> String
$cshow :: RowError -> String
showsPrec :: Int -> RowError -> ShowS
$cshowsPrec :: Int -> RowError -> ShowS
Show, RowError -> RowError -> Bool
(RowError -> RowError -> Bool)
-> (RowError -> RowError -> Bool) -> Eq RowError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RowError -> RowError -> Bool
$c/= :: RowError -> RowError -> Bool
== :: RowError -> RowError -> Bool
$c== :: RowError -> RowError -> Bool
Eq)