graphql-engine/server/src-lib/Hasura/Backends/Postgres/SQL/Error.hs
Auke Booij 4c8ea8e865 Import pg-client-hs as PG
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)

Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)

After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.

PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 19:55:51 +00:00

119 lines
3.7 KiB
Haskell
Raw Blame History

This file contains ambiguous Unicode characters

This file contains Unicode characters that might be confused with other characters. If you think that this is intentional, you can safely ignore this warning. Use the Escape button to reveal them.

{-# LANGUAGE TemplateHaskell #-}
-- | Postgres SQL Error
--
-- Functions and datatypes for interpreting Postgres errors.
module Hasura.Backends.Postgres.SQL.Error
( PGErrorType (..),
_PGDataException,
_PGIntegrityConstraintViolation,
_PGSyntaxErrorOrAccessRuleViolation,
_PGTransactionRollback,
pgErrorType,
PGErrorCode (..),
_PGErrorGeneric,
_PGErrorSpecific,
PGDataException (..),
PGIntegrityConstraintViolation (..),
PGSyntaxErrorOrAccessRuleViolation (..),
PGTransactionRollback (..),
)
where
import Control.Lens.TH (makePrisms)
import Data.Text qualified as T
import Database.PG.Query.Connection qualified as PG
import Hasura.Prelude
-- | The top-level error code type. Errors in Postgres are divided into different /classes/, which
-- are further subdivided into individual error codes. Even if a particular status code is not known
-- to the application, its possible to determine its class and handle it appropriately.
data PGErrorType
= PGDataException (Maybe (PGErrorCode PGDataException))
| PGIntegrityConstraintViolation (Maybe (PGErrorCode PGIntegrityConstraintViolation))
| PGSyntaxErrorOrAccessRuleViolation (Maybe (PGErrorCode PGSyntaxErrorOrAccessRuleViolation))
| PGTransactionRollback (Maybe (PGErrorCode PGTransactionRollback))
deriving (Show, Eq)
data PGErrorCode a
= -- | represents errors that have the non-specific @000@ status code
PGErrorGeneric
| -- | represents errors with a known, more specific status code
PGErrorSpecific a
deriving (Show, Eq, Functor)
data PGDataException
= PGInvalidDatetimeFormat
| PGInvalidParameterValue
| PGInvalidEscapeSequence
| PGInvalidTextRepresentation
deriving (Show, Eq)
data PGIntegrityConstraintViolation
= PGRestrictViolation
| PGNotNullViolation
| PGForeignKeyViolation
| PGUniqueViolation
| PGCheckViolation
| PGExclusionViolation
deriving (Show, Eq)
data PGSyntaxErrorOrAccessRuleViolation
= PGUndefinedObject
| PGInvalidColumnReference
deriving (Show, Eq)
data PGTransactionRollback
= PGSerializationFailure
deriving (Show, Eq)
$(makePrisms ''PGErrorType)
$(makePrisms ''PGErrorCode)
pgErrorType :: PG.PGStmtErrDetail -> Maybe PGErrorType
pgErrorType errorDetails = do
parseTypes =<< PG.edStatusCode errorDetails
where
parseTypes fullCodeText =
choice
[ withClass
"22"
PGDataException
[ code "007" PGInvalidDatetimeFormat,
code "023" PGInvalidParameterValue,
code "025" PGInvalidEscapeSequence,
code "P02" PGInvalidTextRepresentation
],
withClass
"23"
PGIntegrityConstraintViolation
[ code "001" PGRestrictViolation,
code "502" PGNotNullViolation,
code "503" PGForeignKeyViolation,
code "505" PGUniqueViolation,
code "514" PGCheckViolation,
code "P01" PGExclusionViolation
],
withClass
"40"
PGTransactionRollback
[ code "001" PGSerializationFailure
],
withClass
"42"
PGSyntaxErrorOrAccessRuleViolation
[ code "704" PGUndefinedObject,
code "P10" PGInvalidColumnReference
]
]
where
(classText, codeText) = T.splitAt 2 fullCodeText
withClass :: Text -> (Maybe a -> b) -> [Maybe a] -> Maybe b
withClass expectedClassText mkClass codes =
guard (classText == expectedClassText) $> mkClass (choice codes)
code :: Text -> a -> Maybe (PGErrorCode a)
code expectedCodeText codeValue =
guard (codeText == expectedCodeText) $> PGErrorSpecific codeValue