{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE Safe #-}
module Futhark.Error
  ( CompilerError(..)
  , ErrorClass(..)
  , externalError
  , externalErrorS
  , InternalError(..)
  , compilerBug
  , compilerBugS
  , compilerLimitation
  , compilerLimitationS
  , internalErrorS
  )
where
import Control.Exception
import Control.Monad.Error.Class
import qualified Data.Text as T
import Futhark.Util.Pretty
data ErrorClass = CompilerBug
                | CompilerLimitation
                deriving (ErrorClass -> ErrorClass -> Bool
(ErrorClass -> ErrorClass -> Bool)
-> (ErrorClass -> ErrorClass -> Bool) -> Eq ErrorClass
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ErrorClass -> ErrorClass -> Bool
$c/= :: ErrorClass -> ErrorClass -> Bool
== :: ErrorClass -> ErrorClass -> Bool
$c== :: ErrorClass -> ErrorClass -> Bool
Eq, Eq ErrorClass
Eq ErrorClass
-> (ErrorClass -> ErrorClass -> Ordering)
-> (ErrorClass -> ErrorClass -> Bool)
-> (ErrorClass -> ErrorClass -> Bool)
-> (ErrorClass -> ErrorClass -> Bool)
-> (ErrorClass -> ErrorClass -> Bool)
-> (ErrorClass -> ErrorClass -> ErrorClass)
-> (ErrorClass -> ErrorClass -> ErrorClass)
-> Ord ErrorClass
ErrorClass -> ErrorClass -> Bool
ErrorClass -> ErrorClass -> Ordering
ErrorClass -> ErrorClass -> ErrorClass
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ErrorClass -> ErrorClass -> ErrorClass
$cmin :: ErrorClass -> ErrorClass -> ErrorClass
max :: ErrorClass -> ErrorClass -> ErrorClass
$cmax :: ErrorClass -> ErrorClass -> ErrorClass
>= :: ErrorClass -> ErrorClass -> Bool
$c>= :: ErrorClass -> ErrorClass -> Bool
> :: ErrorClass -> ErrorClass -> Bool
$c> :: ErrorClass -> ErrorClass -> Bool
<= :: ErrorClass -> ErrorClass -> Bool
$c<= :: ErrorClass -> ErrorClass -> Bool
< :: ErrorClass -> ErrorClass -> Bool
$c< :: ErrorClass -> ErrorClass -> Bool
compare :: ErrorClass -> ErrorClass -> Ordering
$ccompare :: ErrorClass -> ErrorClass -> Ordering
$cp1Ord :: Eq ErrorClass
Ord, Int -> ErrorClass -> ShowS
[ErrorClass] -> ShowS
ErrorClass -> String
(Int -> ErrorClass -> ShowS)
-> (ErrorClass -> String)
-> ([ErrorClass] -> ShowS)
-> Show ErrorClass
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ErrorClass] -> ShowS
$cshowList :: [ErrorClass] -> ShowS
show :: ErrorClass -> String
$cshow :: ErrorClass -> String
showsPrec :: Int -> ErrorClass -> ShowS
$cshowsPrec :: Int -> ErrorClass -> ShowS
Show)
data CompilerError =
    ExternalError Doc
    
    
  | InternalError T.Text T.Text ErrorClass
    
    
instance Show CompilerError where
  show :: CompilerError -> String
show (ExternalError Doc
s) = Doc -> String
forall a. Pretty a => a -> String
pretty Doc
s
  show (InternalError Text
s Text
_ ErrorClass
_) = Text -> String
T.unpack Text
s
externalError :: MonadError CompilerError m => Doc -> m a
externalError :: Doc -> m a
externalError = CompilerError -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (CompilerError -> m a) -> (Doc -> CompilerError) -> Doc -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc -> CompilerError
ExternalError
externalErrorS :: MonadError CompilerError m => String -> m a
externalErrorS :: String -> m a
externalErrorS = Doc -> m a
forall (m :: * -> *) a. MonadError CompilerError m => Doc -> m a
externalError (Doc -> m a) -> (String -> Doc) -> String -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Doc
text
internalErrorS :: MonadError CompilerError m => String -> Doc -> m a
internalErrorS :: String -> Doc -> m a
internalErrorS String
s Doc
d =
  CompilerError -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (CompilerError -> m a) -> CompilerError -> m a
forall a b. (a -> b) -> a -> b
$ Text -> Text -> ErrorClass -> CompilerError
InternalError (String -> Text
T.pack String
s) (Doc -> Text
forall a. Pretty a => a -> Text
prettyText Doc
d) ErrorClass
CompilerBug
data InternalError = Error ErrorClass T.Text
  deriving (Int -> InternalError -> ShowS
[InternalError] -> ShowS
InternalError -> String
(Int -> InternalError -> ShowS)
-> (InternalError -> String)
-> ([InternalError] -> ShowS)
-> Show InternalError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InternalError] -> ShowS
$cshowList :: [InternalError] -> ShowS
show :: InternalError -> String
$cshow :: InternalError -> String
showsPrec :: Int -> InternalError -> ShowS
$cshowsPrec :: Int -> InternalError -> ShowS
Show)
instance Exception InternalError
compilerBug :: T.Text -> a
compilerBug :: Text -> a
compilerBug = InternalError -> a
forall a e. Exception e => e -> a
throw (InternalError -> a) -> (Text -> InternalError) -> Text -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ErrorClass -> Text -> InternalError
Error ErrorClass
CompilerBug
compilerLimitation :: T.Text -> a
compilerLimitation :: Text -> a
compilerLimitation = InternalError -> a
forall a e. Exception e => e -> a
throw (InternalError -> a) -> (Text -> InternalError) -> Text -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ErrorClass -> Text -> InternalError
Error ErrorClass
CompilerLimitation
compilerBugS :: String -> a
compilerBugS :: String -> a
compilerBugS = Text -> a
forall a. Text -> a
compilerBug (Text -> a) -> (String -> Text) -> String -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack
compilerLimitationS :: String -> a
compilerLimitationS :: String -> a
compilerLimitationS = Text -> a
forall a. Text -> a
compilerLimitation (Text -> a) -> (String -> Text) -> String -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack