Copyright | (c) The University of Glasgow 1998-2002 |
---|---|
License | see libraries/base/LICENSE |
Maintainer | cvs-ghc@haskell.org |
Stability | internal |
Portability | non-portable (GHC extensions) |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Exceptions and exception-handling functions.
Synopsis
- module GHC.Exception.Type
- throw :: forall (r :: RuntimeRep). forall (a :: TYPE r). forall e. Exception e => e -> a
- data ErrorCall where
- errorCallException :: String -> SomeException
- errorCallWithCallStackException :: String -> CallStack -> SomeException
- data CallStack
- fromCallSiteList :: [([Char], SrcLoc)] -> CallStack
- getCallStack :: CallStack -> [([Char], SrcLoc)]
- prettyCallStack :: CallStack -> String
- prettyCallStackLines :: CallStack -> [String]
- showCCSStack :: [String] -> [String]
- data SrcLoc = SrcLoc {
- srcLocPackage :: [Char]
- srcLocModule :: [Char]
- srcLocFile :: [Char]
- srcLocStartLine :: Int
- srcLocStartCol :: Int
- srcLocEndLine :: Int
- srcLocEndCol :: Int
- prettySrcLoc :: SrcLoc -> String
Documentation
module GHC.Exception.Type
throw :: forall (r :: RuntimeRep). forall (a :: TYPE r). forall e. Exception e => e -> a Source #
Throw an exception. Exceptions may be thrown from purely
functional code, but may only be caught within the IO
monad.
WARNING: You may want to use throwIO
instead so that your pure code
stays exception-free.
This is thrown when the user calls error
. The first String
is the
argument given to error
, second String
is the location.
Instances
Exception ErrorCall Source # | Since: base-4.0.0.0 |
Defined in GHC.Exception | |
Show ErrorCall Source # | Since: base-4.0.0.0 |
Eq ErrorCall Source # | Since: base-4.7.0.0 |
Ord ErrorCall Source # | Since: base-4.7.0.0 |
Defined in GHC.Exception |
CallStack
s are a lightweight method of obtaining a
partial call-stack at any point in the program.
A function can request its call-site with the HasCallStack
constraint.
For example, we can define
putStrLnWithCallStack :: HasCallStack => String -> IO ()
as a variant of putStrLn
that will get its call-site and print it,
along with the string given as argument. We can access the
call-stack inside putStrLnWithCallStack
with callStack
.
>>>
:{
putStrLnWithCallStack :: HasCallStack => String -> IO () putStrLnWithCallStack msg = do putStrLn msg putStrLn (prettyCallStack callStack) :}
Thus, if we call putStrLnWithCallStack
we will get a formatted call-stack
alongside our string.
>>>
putStrLnWithCallStack "hello"
hello CallStack (from HasCallStack): putStrLnWithCallStack, called at <interactive>:... in interactive:Ghci...
GHC solves HasCallStack
constraints in three steps:
- If there is a
CallStack
in scope -- i.e. the enclosing function has aHasCallStack
constraint -- GHC will append the new call-site to the existingCallStack
. - If there is no
CallStack
in scope -- e.g. in the GHCi session above -- and the enclosing definition does not have an explicit type signature, GHC will infer aHasCallStack
constraint for the enclosing definition (subject to the monomorphism restriction). - If there is no
CallStack
in scope and the enclosing definition has an explicit type signature, GHC will solve theHasCallStack
constraint for the singletonCallStack
containing just the current call-site.
CallStack
s do not interact with the RTS and do not require compilation
with -prof
. On the other hand, as they are built up explicitly via the
HasCallStack
constraints, they will generally not contain as much
information as the simulated call-stacks maintained by the RTS.
A CallStack
is a [(String, SrcLoc)]
. The String
is the name of
function that was called, the SrcLoc
is the call-site. The list is
ordered with the most recently called function at the head.
NOTE: The intrepid user may notice that HasCallStack
is just an
alias for an implicit parameter ?callStack :: CallStack
. This is an
implementation detail and should not be considered part of the
CallStack
API, we may decide to change the implementation in the
future.
Since: base-4.8.1.0
fromCallSiteList :: [([Char], SrcLoc)] -> CallStack Source #
Convert a list of call-sites to a CallStack
.
Since: base-4.9.0.0
getCallStack :: CallStack -> [([Char], SrcLoc)] Source #
Extract a list of call-sites from the CallStack
.
The list is ordered by most recent call.
Since: base-4.8.1.0
prettyCallStackLines :: CallStack -> [String] Source #
showCCSStack :: [String] -> [String] Source #
A single location in the source code.
Since: base-4.8.1.0
SrcLoc | |
|