{-# LANGUAGE CPP #-}
{-# LANGUAGE QuasiQuotes #-}
module Clash.GHC.Util where
#if MIN_VERSION_ghc(9,0,0)
import GHC.Utils.Outputable (SDoc)
import GHC.Utils.Error (mkPlainErrMsg)
import GHC.Plugins
(DynFlags, SourceError, ($$), blankLine, empty, isGoodSrcSpan, liftIO,
noSrcSpan, text, throwOneError)
#else
import Outputable (SDoc)
import ErrUtils (mkPlainErrMsg)
import GhcPlugins (DynFlags, SourceError, ($$), blankLine, empty, isGoodSrcSpan, liftIO, noSrcSpan, text, throwOneError)
#endif
import GHC (GhcMonad(..), printException)
import Control.Exception (Exception(..), ErrorCall(..))
import GHC.Exception (SomeException)
import System.Exit (ExitCode(ExitFailure), exitWith)
import Clash.Util (ClashException(..))
import Clash.Util.Interpolate (i)
import Clash.Driver.Types (ClashOpts(..))
textLines :: String -> SDoc
textLines :: String -> SDoc
textLines String
s = (SDoc -> SDoc -> SDoc) -> [SDoc] -> SDoc
forall (t :: Type -> Type) a.
Foldable t =>
(a -> a -> a) -> t a -> a
foldl1 SDoc -> SDoc -> SDoc
($$) ((String -> SDoc) -> [String] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map String -> SDoc
text (String -> [String]
lines String
s))
handleClashException
:: GhcMonad m
=> DynFlags
-> ClashOpts
-> SomeException
-> m a
handleClashException :: DynFlags -> ClashOpts -> SomeException -> m a
handleClashException DynFlags
df ClashOpts
opts SomeException
e = case SomeException -> Maybe ClashException
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e of
Just (ClashException SrcSpan
sp String
s Maybe String
eM) -> do
let srcInfo' :: SDoc
srcInfo' | SrcSpan -> Bool
isGoodSrcSpan SrcSpan
sp = SDoc
srcInfo
| Bool
otherwise = SDoc
empty
ErrMsg -> m a
forall (io :: Type -> Type) a. MonadIO io => ErrMsg -> io a
throwOneError (DynFlags -> SrcSpan -> SDoc -> ErrMsg
mkPlainErrMsg DynFlags
df SrcSpan
sp (SDoc
blankLine SDoc -> SDoc -> SDoc
$$ String -> SDoc
textLines String
s SDoc -> SDoc -> SDoc
$$ SDoc
blankLine SDoc -> SDoc -> SDoc
$$ SDoc
srcInfo' SDoc -> SDoc -> SDoc
$$ Bool -> Maybe String -> SDoc
showExtra (ClashOpts -> Bool
opt_errorExtra ClashOpts
opts) Maybe String
eM))
Maybe ClashException
_ -> case SomeException -> Maybe ErrorCall
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e of
Just (ErrorCallWithLocation String
_ String
_) ->
ErrMsg -> m a
forall (io :: Type -> Type) a. MonadIO io => ErrMsg -> io a
throwOneError (DynFlags -> SrcSpan -> SDoc -> ErrMsg
mkPlainErrMsg DynFlags
df SrcSpan
noSrcSpan (String -> SDoc
text String
"Clash error call:" SDoc -> SDoc -> SDoc
$$ String -> SDoc
textLines (SomeException -> String
forall a. Show a => a -> String
show SomeException
e)))
Maybe ErrorCall
_ -> case SomeException -> Maybe SourceError
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e of
Just (SourceError
e' :: SourceError) -> do
SourceError -> m ()
forall (m :: Type -> Type). GhcMonad m => SourceError -> m ()
GHC.printException SourceError
e'
IO a -> m a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO a -> m a) -> IO a -> m a
forall a b. (a -> b) -> a -> b
$ ExitCode -> IO a
forall a. ExitCode -> IO a
exitWith (Int -> ExitCode
ExitFailure Int
1)
Maybe SourceError
_ -> ErrMsg -> m a
forall (io :: Type -> Type) a. MonadIO io => ErrMsg -> io a
throwOneError (DynFlags -> SrcSpan -> SDoc -> ErrMsg
mkPlainErrMsg DynFlags
df SrcSpan
noSrcSpan (String -> SDoc
text String
"Other error:" SDoc -> SDoc -> SDoc
$$ String -> SDoc
textLines (SomeException -> String
forall e. Exception e => e -> String
displayException SomeException
e)))
where
srcInfo :: SDoc
srcInfo = String -> SDoc
textLines [i|
The source location of the error is not exact, only indicative, as it
is acquired after optimizations. The actual location of the error can be
in a function that is inlined. To prevent inlining of those functions,
annotate them with a NOINLINE pragma.
|]
showExtra :: Bool -> Maybe String -> SDoc
showExtra Bool
False (Just String
_) =
SDoc
blankLine SDoc -> SDoc -> SDoc
$$
String -> SDoc
text String
"This error contains additional information, rerun with '-fclash-error-extra' to show this information."
showExtra Bool
True (Just String
msg) =
SDoc
blankLine SDoc -> SDoc -> SDoc
$$
String -> SDoc
text String
"Additional information:" SDoc -> SDoc -> SDoc
$$ SDoc
blankLine SDoc -> SDoc -> SDoc
$$
String -> SDoc
textLines String
msg
showExtra Bool
_ Maybe String
_ = SDoc
empty