{-# LANGUAGE TemplateHaskell #-}
module Preql.Wire.Errors where
import Preql.Imports
import Preql.Wire.Orphans ()
import Data.Aeson.TH (defaultOptions, deriveJSON)
import qualified Database.PostgreSQL.LibPQ as PQ
data UnlocatedFieldError
= UnexpectedNull
| ParseFailure Text
deriving (UnlocatedFieldError -> UnlocatedFieldError -> Bool
(UnlocatedFieldError -> UnlocatedFieldError -> Bool)
-> (UnlocatedFieldError -> UnlocatedFieldError -> Bool)
-> Eq UnlocatedFieldError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnlocatedFieldError -> UnlocatedFieldError -> Bool
$c/= :: UnlocatedFieldError -> UnlocatedFieldError -> Bool
== :: UnlocatedFieldError -> UnlocatedFieldError -> Bool
$c== :: UnlocatedFieldError -> UnlocatedFieldError -> Bool
Eq, Int -> UnlocatedFieldError -> ShowS
[UnlocatedFieldError] -> ShowS
UnlocatedFieldError -> String
(Int -> UnlocatedFieldError -> ShowS)
-> (UnlocatedFieldError -> String)
-> ([UnlocatedFieldError] -> ShowS)
-> Show UnlocatedFieldError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UnlocatedFieldError] -> ShowS
$cshowList :: [UnlocatedFieldError] -> ShowS
show :: UnlocatedFieldError -> String
$cshow :: UnlocatedFieldError -> String
showsPrec :: Int -> UnlocatedFieldError -> ShowS
$cshowsPrec :: Int -> UnlocatedFieldError -> ShowS
Show, Typeable)
$(deriveJSON defaultOptions ''UnlocatedFieldError)
data FieldError = FieldError
{ FieldError -> Int
errorRow :: Int
, FieldError -> Int
errorColumn :: Int
, FieldError -> UnlocatedFieldError
failure :: UnlocatedFieldError
} deriving (FieldError -> FieldError -> Bool
(FieldError -> FieldError -> Bool)
-> (FieldError -> FieldError -> Bool) -> Eq FieldError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FieldError -> FieldError -> Bool
$c/= :: FieldError -> FieldError -> Bool
== :: FieldError -> FieldError -> Bool
$c== :: FieldError -> FieldError -> Bool
Eq, Int -> FieldError -> ShowS
[FieldError] -> ShowS
FieldError -> String
(Int -> FieldError -> ShowS)
-> (FieldError -> String)
-> ([FieldError] -> ShowS)
-> Show FieldError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FieldError] -> ShowS
$cshowList :: [FieldError] -> ShowS
show :: FieldError -> String
$cshow :: FieldError -> String
showsPrec :: Int -> FieldError -> ShowS
$cshowsPrec :: Int -> FieldError -> ShowS
Show, Typeable)
instance Exception FieldError
$(deriveJSON defaultOptions ''FieldError)
data PgType = Oid PQ.Oid
| TypeName Text
deriving (PgType -> PgType -> Bool
(PgType -> PgType -> Bool)
-> (PgType -> PgType -> Bool) -> Eq PgType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PgType -> PgType -> Bool
$c/= :: PgType -> PgType -> Bool
== :: PgType -> PgType -> Bool
$c== :: PgType -> PgType -> Bool
Eq, Int -> PgType -> ShowS
[PgType] -> ShowS
PgType -> String
(Int -> PgType -> ShowS)
-> (PgType -> String) -> ([PgType] -> ShowS) -> Show PgType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PgType] -> ShowS
$cshowList :: [PgType] -> ShowS
show :: PgType -> String
$cshow :: PgType -> String
showsPrec :: Int -> PgType -> ShowS
$cshowsPrec :: Int -> PgType -> ShowS
Show, Typeable)
$(deriveJSON defaultOptions ''PgType)
data TypeMismatch = TypeMismatch
{ TypeMismatch -> PgType
expected :: PgType
, TypeMismatch -> Oid
actual :: PQ.Oid
, TypeMismatch -> Int
column :: Int
, TypeMismatch -> Maybe Text
columnName :: Maybe Text
} deriving (TypeMismatch -> TypeMismatch -> Bool
(TypeMismatch -> TypeMismatch -> Bool)
-> (TypeMismatch -> TypeMismatch -> Bool) -> Eq TypeMismatch
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeMismatch -> TypeMismatch -> Bool
$c/= :: TypeMismatch -> TypeMismatch -> Bool
== :: TypeMismatch -> TypeMismatch -> Bool
$c== :: TypeMismatch -> TypeMismatch -> Bool
Eq, Int -> TypeMismatch -> ShowS
[TypeMismatch] -> ShowS
TypeMismatch -> String
(Int -> TypeMismatch -> ShowS)
-> (TypeMismatch -> String)
-> ([TypeMismatch] -> ShowS)
-> Show TypeMismatch
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TypeMismatch] -> ShowS
$cshowList :: [TypeMismatch] -> ShowS
show :: TypeMismatch -> String
$cshow :: TypeMismatch -> String
showsPrec :: Int -> TypeMismatch -> ShowS
$cshowsPrec :: Int -> TypeMismatch -> ShowS
Show, Typeable)
$(deriveJSON defaultOptions ''TypeMismatch)
data QueryError
= ConnectionError Text
| DecoderError FieldError
| PgTypeMismatch [TypeMismatch]
deriving (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, 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, Typeable)
instance Exception QueryError
$(deriveJSON defaultOptions ''QueryError)