--------------------------------------------------------------------------------
-- Copyright © 2011 National Institute of Aerospace / Galois, Inc.
--------------------------------------------------------------------------------

{-# LANGUAGE Safe #-}

-- | Custom functions to report error messages to users.
module Copilot.Core.Error
  ( impossible
  , badUsage ) where

-- | Report an error due to a bug in Copilot.
impossible :: String -- ^ Name of the function in which the error was detected.
           -> String -- ^ Name of the package in which the function is located.
           -> a
impossible :: String -> String -> a
impossible String
function String
package =
  String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"\"Impossible\" error in function "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
function String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
", in package " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
package
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
". Please file an issue at "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"https://github.com/Copilot-Language/copilot/issues"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"or email the maintainers at <dev@dedden.net>"

-- | Report an error due to an error detected by Copilot (e.g., user error).
badUsage :: String -- ^ Description of the error.
         -> a
badUsage :: String -> a
badUsage String
msg = String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"Copilot error: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
msg