{-# LANGUAGE OverloadedStrings #-}
module Data.Error
  ( Error,
    newError,
    addContext,
    prettyError,
    unwrapError,
    expectError,
  )
where

import Data.Function ((&))
import Data.Text (Text)
import qualified Data.Text as Text

-- | The canonical @Error@ type.
--
-- It can be
--
-- * created from a human-readable error message ('newError')
-- * more semantic context can be added to an existing @Error@ ('addContext')
-- * pretty-printed (`prettyError`)
newtype Error = Error [Text]

-- | Create an ad-hoc 'Error' from an error message.
newError :: Text -> Error
newError :: Text -> Error
newError Text
msg = [Text] -> Error
Error [Text
msg]

-- | Add a higher-level context to an 'Error'.
--
-- For example, your code hits a “file not found” I/O exception.
-- Instead of propagating it unseen, you catch it and annotate it with 'addContext',
-- and describe why you wanted to open the file in the first place:
--
-- @
-- addContext "Trying to open config file"
--   $ newError "file not found: ./foo"
-- @
--
-- This way, when a user see the error, they will understand better what happened:
--
-- @
-- "Trying to open config file: file not found: ./foo"
-- @
--
-- See 'prettyError'.
addContext :: Text -> Error -> Error
addContext :: Text -> Error -> Error
addContext Text
e (Error [Text]
es) = [Text] -> Error
Error ([Text] -> Error) -> [Text] -> Error
forall a b. (a -> b) -> a -> b
$ Text
e Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text]
es

-- | Pretty print the error.
--
-- It will print all context messages, starting with the outermost.
--
-- Example:
--
-- @
-- prettyError $ newError "file not found: ./foo"
--
-- ==> "file not found: ./foo"
--
-- prettyError
--   $ addContext "Trying to open config file"
--     $ newError "file not found: ./foo"
--
-- ==> "Trying to open config file: file not found: ./foo"
-- @
prettyError :: Error -> Text
prettyError :: Error -> Text
prettyError (Error [Text]
es) = Text -> [Text] -> Text
Text.intercalate Text
": " [Text]
es

-- | Return the value from a potentially failing computation.
--
-- Abort with the 'Error's message if it was a 'Left'.
--
-- Panic: if Error
--
-- Example:
--
-- @
-- unwrapError $ Left (newError "oh no!")
--
-- ==> *** Exception: oh no!
--
-- unwrapError $ Right 42
--
-- ==> 42
-- @
unwrapError :: Either Error p -> p
unwrapError :: Either Error p -> p
unwrapError Either Error p
e = case Either Error p
e of
  Left Error
err -> [Char] -> p
forall a. HasCallStack => [Char] -> a
error (Error -> Text
prettyError Error
err Text -> (Text -> [Char]) -> [Char]
forall a b. a -> (a -> b) -> b
& Text -> [Char]
Text.unpack)
  Right p
a -> p
a

-- | Return the value from a potentially failing computation.
--
-- Abort with the error message if it was an error.
--
-- The text message is added to the 'Error' as additional context before aborting.
--
-- Panic: if Error
--
-- Example:
--
-- @
-- exceptError "something bad happened" $ Left (newError "oh no!")
--
-- ==> *** Exception: something bad happened: oh no!
--
-- exceptError $ Right 42
--
-- ==> 42
-- @
expectError :: Text -> Either Error p -> p
expectError :: Text -> Either Error p -> p
expectError Text
context Either Error p
e = case Either Error p
e of
  Left Error
err ->
    [Char] -> p
forall a. HasCallStack => [Char] -> a
error
      ( Error
err
          Error -> (Error -> Error) -> Error
forall a b. a -> (a -> b) -> b
& Text -> Error -> Error
addContext Text
context
          Error -> (Error -> Text) -> Text
forall a b. a -> (a -> b) -> b
& Error -> Text
prettyError
          Text -> (Text -> [Char]) -> [Char]
forall a b. a -> (a -> b) -> b
& Text -> [Char]
Text.unpack
      )
  Right p
a -> p
a