Skip to content

Commit

Permalink
QueryError: add displayException
Browse files Browse the repository at this point in the history
  • Loading branch information
domenkozar committed Jan 4, 2024
1 parent b8d95d5 commit 915d9a2
Showing 1 changed file with 53 additions and 1 deletion.
54 changes: 53 additions & 1 deletion library/Hasql/Private/Errors.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,14 +12,66 @@ module Hasql.Private.Errors where

import Hasql.Private.Prelude

import qualified Data.ByteString.Char8 as BC


-- |
-- An error during the execution of a query.
-- Comes packed with the query template and a textual representation of the provided params.
data QueryError
= QueryError ByteString [Text] CommandError
deriving (Show, Eq, Typeable)

instance Exception QueryError
instance Exception QueryError where
displayException (QueryError query params commandError) =
let
queryContext :: Maybe (ByteString, Int)
queryContext = case commandError of
ClientError _ -> Nothing
ResultError resultError -> case resultError of
ServerError _ message _ _ (Just position) -> Just (message, position)
_ -> Nothing

-- Function to find the line number and position within the line
findLineAndPos :: ByteString -> Int -> (Int, Int)
findLineAndPos byteString errorPos =
let (_, line, pos) = BC.foldl' (\(total, line, pos) c ->
case total + 1 of
0 -> (total, line, pos)
cursor | cursor == errorPos -> (-1, line, pos + 1)
| c == '\n' -> (total + 1, line + 1, 0)
| otherwise -> (total + 1, line, pos + 1)
) (0, 1, 0) byteString
in (line, pos)

formatErrorContext :: ByteString -> ByteString -> Int -> ByteString
formatErrorContext query message errorPos =
let lines = BC.lines query
(lineNum, linePos) = findLineAndPos query errorPos
in BC.unlines (take lineNum lines) <> BC.replicate (linePos - 1) ' '
<> "^ " <> message

prettyQuery :: ByteString
prettyQuery = case queryContext of
Nothing -> query
Just (message, pos) -> formatErrorContext query message pos

in "QueryError!\n"
<> "\n Query:\n" <> BC.unpack prettyQuery <> "\n"
<> "\n Params: " <> show params
<> "\n Error: " <> case commandError of
ClientError (Just message) -> "Client error: " <> show message
ClientError Nothing -> "Unknown client error"
ResultError resultError -> case resultError of
ServerError code message details hint position ->
"Server error " <> BC.unpack code
<> maybe "" (\d -> "\n Details: " <> BC.unpack d) details
<> maybe "" (\h -> "\n Hint: " <> BC.unpack h) hint
UnexpectedResult message -> "Unexpected result: " <> show message
RowError row column rowError ->
"Row error: " <> show row <> ":" <> show column <> " " <> show rowError
UnexpectedAmountOfRows amount ->
"Unexpected amount of rows: " <> show amount

-- |
-- An error of some command in the session.
Expand Down

0 comments on commit 915d9a2

Please sign in to comment.