{-# 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 (Eq, Show, Typeable)
$(deriveJSON defaultOptions ''UnlocatedFieldError)
data FieldError = FieldError
{ errorRow :: Int
, errorColumn :: Int
, failure :: UnlocatedFieldError
} deriving (Eq, Show, Typeable)
instance Exception FieldError
$(deriveJSON defaultOptions ''FieldError)
data TypeMismatch = TypeMismatch
{ expected :: PQ.Oid
, actual :: PQ.Oid
, column :: Int
, columnName :: Maybe Text
} deriving (Eq, Show, Typeable)
$(deriveJSON defaultOptions ''TypeMismatch)
data QueryError
= ConnectionError Text
| DecoderError FieldError
| PgTypeMismatch [TypeMismatch]
deriving (Eq, Show, Typeable)
instance Exception QueryError
$(deriveJSON defaultOptions ''QueryError)