Skip to content

Commit a1009d1

Browse files
authored
refactor: separate SchemaCacheError from ApiRequestError (PostgREST#4010)
1 parent a6e81a5 commit a1009d1

File tree

3 files changed

+109
-84
lines changed

3 files changed

+109
-84
lines changed

src/PostgREST/Error.hs

Lines changed: 65 additions & 40 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@ module PostgREST.Error
1010
, ApiRequestError(..)
1111
, QPError(..)
1212
, RangeError(..)
13+
, SchemaCacheError(..)
1314
, PgError(..)
1415
, Error(..)
1516
, JwtError (..)
@@ -69,16 +70,12 @@ class ErrorBody a where
6970

7071
data ApiRequestError
7172
= AggregatesNotAllowed
72-
| AmbiguousRelBetween Text Text [Relationship]
73-
| AmbiguousRpc [Routine]
7473
| MediaTypeError [ByteString]
7574
| InvalidBody ByteString
7675
| InvalidFilters
7776
| InvalidPreferences [ByteString]
7877
| InvalidRange RangeError
7978
| InvalidRpcMethod ByteString
80-
| NoRelBetween Text Text (Maybe Text) Text RelationshipsMap
81-
| NoRpc Text Text [Text] MediaType Bool [QualifiedIdentifier] [Routine]
8279
| NotEmbedded Text
8380
| NotImplemented Text
8481
| PutLimitNotAllowedError
@@ -87,8 +84,6 @@ data ApiRequestError
8784
| UnacceptableFilter Text
8885
| UnacceptableSchema [Text]
8986
| UnsupportedMethod ByteString
90-
| ColumnNotFound Text Text
91-
| TableNotFound Text Text [Table]
9287
| GucHeadersError
9388
| GucStatusError
9489
| PutMatchingPkError
@@ -116,17 +111,13 @@ data RangeError
116111

117112
instance PgrstError ApiRequestError where
118113
status AggregatesNotAllowed{} = HTTP.status400
119-
status AmbiguousRelBetween{} = HTTP.status300
120-
status AmbiguousRpc{} = HTTP.status300
121114
status MediaTypeError{} = HTTP.status406
122115
status InvalidBody{} = HTTP.status400
123116
status InvalidFilters = HTTP.status405
124117
status InvalidPreferences{} = HTTP.status400
125118
status InvalidRpcMethod{} = HTTP.status405
126119
status InvalidRange{} = HTTP.status416
127120

128-
status NoRelBetween{} = HTTP.status400
129-
status NoRpc{} = HTTP.status404
130121
status NotEmbedded{} = HTTP.status400
131122
status NotImplemented{} = HTTP.status400
132123
status PutLimitNotAllowedError = HTTP.status400
@@ -135,8 +126,6 @@ instance PgrstError ApiRequestError where
135126
status UnacceptableFilter{} = HTTP.status400
136127
status UnacceptableSchema{} = HTTP.status406
137128
status UnsupportedMethod{} = HTTP.status405
138-
status ColumnNotFound{} = HTTP.status400
139-
status TableNotFound{} = HTTP.status404
140129
status GucHeadersError = HTTP.status500
141130
status GucStatusError = HTTP.status500
142131
status PutMatchingPkError = HTTP.status400
@@ -192,13 +181,6 @@ instance ErrorBody ApiRequestError where
192181
code OpenAPIDisabled = "PGRST126"
193182
code NotImplemented{} = "PGRST127"
194183

195-
code NoRelBetween{} = "PGRST200"
196-
code AmbiguousRelBetween{} = "PGRST201"
197-
code NoRpc{} = "PGRST202"
198-
code AmbiguousRpc{} = "PGRST203"
199-
code ColumnNotFound{} = "PGRST204"
200-
code TableNotFound{} = "PGRST205"
201-
202184
-- MESSAGE: Text
203185
message (QueryParamError (QPError msg _)) = msg
204186
message (InvalidRpcMethod method) = "Cannot use the " <> T.decodeUtf8 method <> " method on RPC"
@@ -224,19 +206,6 @@ instance ErrorBody ApiRequestError where
224206
message OpenAPIDisabled = "Root endpoint metadata is disabled"
225207
message (NotImplemented _) = "Feature not implemented"
226208

227-
message (NoRelBetween parent child _ _ _) = "Could not find a relationship between '" <> parent <> "' and '" <> child <> "' in the schema cache"
228-
message (AmbiguousRelBetween parent child _) = "Could not embed because more than one relationship was found for '" <> parent <> "' and '" <> child <> "'"
229-
message (NoRpc schema procName argumentKeys contentType isInvPost _ _) = "Could not find the function " <> func <> (if onlySingleParams then "" else fmtPrms prmsMsg) <> " in the schema cache"
230-
where
231-
onlySingleParams = isInvPost && contentType `elem` [MTTextPlain, MTTextXML, MTOctetStream]
232-
func = schema <> "." <> procName
233-
prms = T.intercalate ", " argumentKeys
234-
prmsMsg = "(" <> prms <> ")"
235-
fmtPrms p = if null argumentKeys then " without parameters" else p
236-
message (AmbiguousRpc procs) = "Could not choose the best candidate function between: " <> T.intercalate ", " [pdSchema p <> "." <> pdName p <> "(" <> T.intercalate ", " [ppName a <> " => " <> ppType a | a <- pdParams p] <> ")" | p <- procs]
237-
message (ColumnNotFound rel col) = "Could not find the '" <> col <> "' column of '" <> rel <> "' in the schema cache"
238-
message (TableNotFound schemaName relName _) = "Could not find the table '" <> schemaName <> "." <> relName <> "' in the schema cache"
239-
240209
-- DETAILS: Maybe JSON.Value
241210
details (QueryParamError (QPError _ dets)) = Just $ JSON.String dets
242211
details (InvalidRange rangeError) = Just $
@@ -252,6 +221,58 @@ instance ErrorBody ApiRequestError where
252221
details (MaxAffectedViolationError n) = Just $ JSON.String $ T.unwords ["The query affects", show n, "rows"]
253222
details (NotImplemented details') = Just $ JSON.String details'
254223

224+
details _ = Nothing
225+
226+
-- HINT: Maybe JSON.Value
227+
hint (NotEmbedded resource) = Just $ JSON.String $ "Verify that '" <> resource <> "' is included in the 'select' query parameter."
228+
hint (PGRSTParseError raiseErr) = Just $ JSON.String $ pgrstParseErrorHint raiseErr
229+
230+
hint _ = Nothing
231+
232+
instance JSON.ToJSON ApiRequestError where
233+
toJSON err = toJsonPgrstError
234+
(code err) (message err) (details err) (hint err)
235+
236+
data SchemaCacheError
237+
= AmbiguousRelBetween Text Text [Relationship]
238+
| AmbiguousRpc [Routine]
239+
| NoRelBetween Text Text (Maybe Text) Text RelationshipsMap
240+
| NoRpc Text Text [Text] MediaType Bool [QualifiedIdentifier] [Routine]
241+
| ColumnNotFound Text Text
242+
| TableNotFound Text Text [Table]
243+
deriving Show
244+
245+
instance PgrstError SchemaCacheError where
246+
status AmbiguousRelBetween{} = HTTP.status300
247+
status AmbiguousRpc{} = HTTP.status300
248+
status NoRelBetween{} = HTTP.status400
249+
status NoRpc{} = HTTP.status404
250+
status ColumnNotFound{} = HTTP.status400
251+
status TableNotFound{} = HTTP.status404
252+
253+
headers _ = mempty
254+
255+
instance ErrorBody SchemaCacheError where
256+
code NoRelBetween{} = "PGRST200"
257+
code AmbiguousRelBetween{} = "PGRST201"
258+
code NoRpc{} = "PGRST202"
259+
code AmbiguousRpc{} = "PGRST203"
260+
code ColumnNotFound{} = "PGRST204"
261+
code TableNotFound{} = "PGRST205"
262+
263+
message (NoRelBetween parent child _ _ _) = "Could not find a relationship between '" <> parent <> "' and '" <> child <> "' in the schema cache"
264+
message (AmbiguousRelBetween parent child _) = "Could not embed because more than one relationship was found for '" <> parent <> "' and '" <> child <> "'"
265+
message (NoRpc schema procName argumentKeys contentType isInvPost _ _) = "Could not find the function " <> func <> (if onlySingleParams then "" else fmtPrms prmsMsg) <> " in the schema cache"
266+
where
267+
onlySingleParams = isInvPost && contentType `elem` [MTTextPlain, MTTextXML, MTOctetStream]
268+
func = schema <> "." <> procName
269+
prms = T.intercalate ", " argumentKeys
270+
prmsMsg = "(" <> prms <> ")"
271+
fmtPrms p = if null argumentKeys then " without parameters" else p
272+
message (AmbiguousRpc procs) = "Could not choose the best candidate function between: " <> T.intercalate ", " [pdSchema p <> "." <> pdName p <> "(" <> T.intercalate ", " [ppName a <> " => " <> ppType a | a <- pdParams p] <> ")" | p <- procs]
273+
message (ColumnNotFound rel col) = "Could not find the '" <> col <> "' column of '" <> rel <> "' in the schema cache"
274+
message (TableNotFound schemaName relName _) = "Could not find the table '" <> schemaName <> "." <> relName <> "' in the schema cache"
275+
255276
details (NoRelBetween parent child embedHint schema _) = Just $ JSON.String $ "Searched for a foreign key relationship between '" <> parent <> "' and '" <> child <> maybe mempty ("' using the hint '" <>) embedHint <> "' in the schema '" <> schema <> "', but no matches were found."
256277
details (AmbiguousRelBetween _ _ rels) = Just $ JSON.toJSONList (compressedRel <$> rels)
257278
details (NoRpc schema procName argumentKeys contentType isInvPost _ _) =
@@ -271,10 +292,6 @@ instance ErrorBody ApiRequestError where
271292

272293
details _ = Nothing
273294

274-
-- HINT: Maybe JSON.Value
275-
hint (NotEmbedded resource) = Just $ JSON.String $ "Verify that '" <> resource <> "' is included in the 'select' query parameter."
276-
hint (PGRSTParseError raiseErr) = Just $ JSON.String $ pgrstParseErrorHint raiseErr
277-
278295
hint (NoRelBetween parent child _ schema allRels) = JSON.String <$> noRelBetweenHint parent child schema allRels
279296
hint (AmbiguousRelBetween _ child rels) = Just $ JSON.String $ "Try changing '" <> child <> "' to one of the following: " <> relHint rels <> ". Find the desired relationship in the 'details' key."
280297
-- The hint will be null in the case of single unnamed parameter functions
@@ -289,8 +306,7 @@ instance ErrorBody ApiRequestError where
289306

290307
hint _ = Nothing
291308

292-
293-
instance JSON.ToJSON ApiRequestError where
309+
instance JSON.ToJSON SchemaCacheError where
294310
toJSON err = toJsonPgrstError
295311
(code err) (message err) (details err) (hint err)
296312

@@ -461,6 +477,8 @@ pgrstParseErrorHint err = case err of
461477
_ -> "DETAIL must be a JSON object with obligatory keys: 'status', 'headers' and optional key: 'status_text'."
462478

463479
data PgError = PgError Authenticated SQL.UsageError
480+
deriving Show
481+
464482
type Authenticated = Bool
465483

466484
instance PgrstError PgError where
@@ -608,27 +626,30 @@ pgErrorStatus authed (SQL.SessionUsageError (SQL.QueryError _ _ (SQL.ResultError
608626
_ -> HTTP.status500
609627

610628

611-
-- TODO: separate "SchemaCacheError" from ApiRequestError similar to how we
612-
-- group them in docs
613629
data Error
614630
= ApiRequestError ApiRequestError
631+
| SchemaCacheErr SchemaCacheError
615632
| JwtErr JwtError
616633
| NoSchemaCacheError
617634
| PgErr PgError
635+
deriving Show
618636

619637
data JwtError
620638
= JwtDecodeError Text
621639
| JwtSecretMissing
622640
| JwtTokenRequired
623641
| JwtClaimsError Text
642+
deriving Show
624643

625644
instance PgrstError Error where
626645
status (ApiRequestError err) = status err
646+
status (SchemaCacheErr err) = status err
627647
status (JwtErr err) = status err
628648
status NoSchemaCacheError = HTTP.status503
629649
status (PgErr err) = status err
630650

631651
headers (ApiRequestError err) = proxyStatusHeader (code err) : headers err
652+
headers (SchemaCacheErr err) = proxyStatusHeader (code err) : headers err
632653
headers (JwtErr err) = proxyStatusHeader (code err) : headers err
633654
headers (PgErr err) = proxyStatusHeader (code err) : headers err
634655
headers err@NoSchemaCacheError = proxyStatusHeader (code err) : mempty
@@ -639,21 +660,25 @@ instance JSON.ToJSON Error where
639660

640661
instance ErrorBody Error where
641662
code (ApiRequestError err) = code err
663+
code (SchemaCacheErr err) = code err
642664
code (JwtErr err) = code err
643665
code NoSchemaCacheError = "PGRST002"
644666
code (PgErr err) = code err
645667

646668
message (ApiRequestError err) = message err
669+
message (SchemaCacheErr err) = message err
647670
message (JwtErr err) = message err
648671
message NoSchemaCacheError = "Could not query the database for the schema cache. Retrying."
649672
message (PgErr err) = message err
650673

651674
details (ApiRequestError err) = details err
675+
details (SchemaCacheErr err) = details err
652676
details (JwtErr err) = details err
653677
details NoSchemaCacheError = Nothing
654678
details (PgErr err) = details err
655679

656680
hint (ApiRequestError err) = hint err
681+
hint (SchemaCacheErr err) = hint err
657682
hint (JwtErr err) = hint err
658683
hint NoSchemaCacheError = Nothing
659684
hint (PgErr err) = hint err

0 commit comments

Comments
 (0)