{-# Language Trustworthy #-}
{-# Language ImplicitParams #-}
{-# Language TemplateHaskell #-}
module Panic
( Panic(..)
, PanicComponent(..)
, useGitRevision
, HasCallStack
, panic
) where
import Development.GitRev
import Language.Haskell.TH
import Data.Typeable
import Control.Exception(Exception, throw)
import Data.Maybe(fromMaybe,listToMaybe)
import GHC.Stack
panic :: (PanicComponent a, HasCallStack) =>
a ->
String ->
[String] ->
b
panic comp loc msg =
throw Panic { panicComponent = comp
, panicLoc = loc
, panicMsg = msg
, panicStack = freezeCallStack ?callStack
}
data Panic a = Panic { panicComponent :: a
, panicLoc :: String
, panicMsg :: [String]
, panicStack :: CallStack
}
class Typeable a => PanicComponent a where
panicComponentName :: a -> String
panicComponentIssues :: a -> String
panicComponentRevision :: a -> (String,String)
useGitRevision :: Q Exp
useGitRevision = [| \_ -> ($gitHash, $gitBranch ++ $dirty) |]
where dirty = [| if $gitDirty then " (uncommited files present)" else "" |]
instance (PanicComponent a) => Show (Panic a) where
show p = unlines $
[ "You have encountered a bug in " ++
panicComponentName comp ++ "'s implementation."
, "*** Please create an issue at " ++
panicComponentIssues comp
, ""
, "%< --------------------------------------------------- "
] ++ rev ++
[ locLab ++ panicLoc p
, msgLab ++ fromMaybe "" (listToMaybe msgLines)
]
++ map (tabs ++) (drop 1 msgLines)
++ [ prettyCallStack (panicStack p) ] ++
[ "%< --------------------------------------------------- "
]
where comp = panicComponent p
msgLab = " Message: "
locLab = " Location: "
revLab = " Revision: "
branchLab = " Branch: "
msgLines = panicMsg p
tabs = map (const ' ') msgLab
(commitHash,commitBranch) = panicComponentRevision comp
rev | null commitHash = []
| otherwise = [ revLab ++ commitHash
, branchLab ++ commitBranch
]
instance PanicComponent a => Exception (Panic a)