2022-03-16 03:39:21 +03:00
|
|
|
|
{-# LANGUAGE TemplateHaskell #-}
|
|
|
|
|
|
2022-02-08 12:24:34 +03:00
|
|
|
|
-- | Postgres SQL Error
|
|
|
|
|
--
|
|
|
|
|
-- Functions and datatypes for interpreting Postgres errors.
|
2020-10-27 16:53:49 +03:00
|
|
|
|
module Hasura.Backends.Postgres.SQL.Error
|
2021-09-24 01:56:37 +03:00
|
|
|
|
( PGErrorType (..),
|
|
|
|
|
_PGDataException,
|
|
|
|
|
_PGIntegrityConstraintViolation,
|
|
|
|
|
_PGSyntaxErrorOrAccessRuleViolation,
|
2022-03-24 14:50:52 +03:00
|
|
|
|
_PGTransactionRollback,
|
2021-09-24 01:56:37 +03:00
|
|
|
|
pgErrorType,
|
|
|
|
|
PGErrorCode (..),
|
|
|
|
|
_PGErrorGeneric,
|
|
|
|
|
_PGErrorSpecific,
|
|
|
|
|
PGDataException (..),
|
|
|
|
|
PGIntegrityConstraintViolation (..),
|
|
|
|
|
PGSyntaxErrorOrAccessRuleViolation (..),
|
2022-03-24 14:50:52 +03:00
|
|
|
|
PGTransactionRollback (..),
|
2021-09-24 01:56:37 +03:00
|
|
|
|
)
|
|
|
|
|
where
|
2019-08-23 15:57:09 +03:00
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
|
import Control.Lens.TH (makePrisms)
|
|
|
|
|
import Data.Text qualified as T
|
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 22:54:43 +03:00
|
|
|
|
import Database.PG.Query.Connection qualified as PG
|
2021-09-24 01:56:37 +03:00
|
|
|
|
import Hasura.Prelude
|
2020-10-27 16:53:49 +03:00
|
|
|
|
|
2019-07-22 15:47:13 +03:00
|
|
|
|
-- | 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, it’s possible to determine its class and handle it appropriately.
|
2019-08-23 15:57:09 +03:00
|
|
|
|
data PGErrorType
|
2022-07-29 17:05:03 +03:00
|
|
|
|
= PGDataException (Maybe (PGErrorCode PGDataException))
|
|
|
|
|
| PGIntegrityConstraintViolation (Maybe (PGErrorCode PGIntegrityConstraintViolation))
|
|
|
|
|
| PGSyntaxErrorOrAccessRuleViolation (Maybe (PGErrorCode PGSyntaxErrorOrAccessRuleViolation))
|
|
|
|
|
| PGTransactionRollback (Maybe (PGErrorCode PGTransactionRollback))
|
2019-07-22 15:47:13 +03:00
|
|
|
|
deriving (Show, Eq)
|
|
|
|
|
|
2019-08-23 15:57:09 +03:00
|
|
|
|
data PGErrorCode a
|
2021-09-24 01:56:37 +03:00
|
|
|
|
= -- | represents errors that have the non-specific @000@ status code
|
|
|
|
|
PGErrorGeneric
|
|
|
|
|
| -- | represents errors with a known, more specific status code
|
2022-07-29 17:05:03 +03:00
|
|
|
|
PGErrorSpecific a
|
2019-07-22 15:47:13 +03:00
|
|
|
|
deriving (Show, Eq, Functor)
|
|
|
|
|
|
2019-08-23 15:57:09 +03:00
|
|
|
|
data PGDataException
|
|
|
|
|
= PGInvalidDatetimeFormat
|
|
|
|
|
| PGInvalidParameterValue
|
|
|
|
|
| PGInvalidEscapeSequence
|
|
|
|
|
| PGInvalidTextRepresentation
|
2019-07-22 15:47:13 +03:00
|
|
|
|
deriving (Show, Eq)
|
|
|
|
|
|
2019-08-23 15:57:09 +03:00
|
|
|
|
data PGIntegrityConstraintViolation
|
|
|
|
|
= PGRestrictViolation
|
|
|
|
|
| PGNotNullViolation
|
|
|
|
|
| PGForeignKeyViolation
|
|
|
|
|
| PGUniqueViolation
|
|
|
|
|
| PGCheckViolation
|
|
|
|
|
| PGExclusionViolation
|
2019-07-22 15:47:13 +03:00
|
|
|
|
deriving (Show, Eq)
|
|
|
|
|
|
2019-08-23 15:57:09 +03:00
|
|
|
|
data PGSyntaxErrorOrAccessRuleViolation
|
|
|
|
|
= PGUndefinedObject
|
|
|
|
|
| PGInvalidColumnReference
|
2019-07-22 15:47:13 +03:00
|
|
|
|
deriving (Show, Eq)
|
|
|
|
|
|
2022-03-24 14:50:52 +03:00
|
|
|
|
data PGTransactionRollback
|
|
|
|
|
= PGSerializationFailure
|
|
|
|
|
deriving (Show, Eq)
|
|
|
|
|
|
2019-08-23 15:57:09 +03:00
|
|
|
|
$(makePrisms ''PGErrorType)
|
|
|
|
|
$(makePrisms ''PGErrorCode)
|
2019-07-22 15:47:13 +03:00
|
|
|
|
|
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 22:54:43 +03:00
|
|
|
|
pgErrorType :: PG.PGStmtErrDetail -> Maybe PGErrorType
|
2022-03-24 14:50:52 +03:00
|
|
|
|
pgErrorType errorDetails = do
|
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 22:54:43 +03:00
|
|
|
|
parseTypes =<< PG.edStatusCode errorDetails
|
2019-07-22 15:47:13 +03:00
|
|
|
|
where
|
2021-09-24 01:56:37 +03:00
|
|
|
|
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
|
|
|
|
|
],
|
2022-03-24 14:50:52 +03:00
|
|
|
|
withClass
|
|
|
|
|
"40"
|
|
|
|
|
PGTransactionRollback
|
|
|
|
|
[ code "001" PGSerializationFailure
|
|
|
|
|
],
|
2021-09-24 01:56:37 +03:00
|
|
|
|
withClass
|
|
|
|
|
"42"
|
|
|
|
|
PGSyntaxErrorOrAccessRuleViolation
|
|
|
|
|
[ code "704" PGUndefinedObject,
|
|
|
|
|
code "P10" PGInvalidColumnReference
|
|
|
|
|
]
|
2019-07-22 15:47:13 +03:00
|
|
|
|
]
|
|
|
|
|
where
|
|
|
|
|
(classText, codeText) = T.splitAt 2 fullCodeText
|
|
|
|
|
|
2020-10-27 16:53:49 +03:00
|
|
|
|
withClass :: Text -> (Maybe a -> b) -> [Maybe a] -> Maybe b
|
2019-07-22 15:47:13 +03:00
|
|
|
|
withClass expectedClassText mkClass codes =
|
|
|
|
|
guard (classText == expectedClassText) $> mkClass (choice codes)
|
|
|
|
|
|
2020-10-27 16:53:49 +03:00
|
|
|
|
code :: Text -> a -> Maybe (PGErrorCode a)
|
2019-07-22 15:47:13 +03:00
|
|
|
|
code expectedCodeText codeValue =
|
2019-08-23 15:57:09 +03:00
|
|
|
|
guard (codeText == expectedCodeText) $> PGErrorSpecific codeValue
|