Copyright | (c) The University of Glasgow 2015 |
---|---|
License | see libraries/ghc-prim/LICENSE |
Maintainer | ghc-devs@haskell.org |
Stability | internal |
Portability | non-portable (GHC Extensions) |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Type definitions for implicit call-stacks. Use GHC.Stack from the base package instead of importing this module directly.
The API of this module is unstable and not meant to be consumed by the general public.
If you absolutely must depend on it, make sure to use a tight upper
bound, e.g., base < 4.X
rather than base < 5
, because the interface can
change rapidly without much warning.
Synopsis
- data CallStack
- type HasCallStack = ?callStack :: CallStack
- emptyCallStack :: CallStack
- freezeCallStack :: CallStack -> CallStack
- fromCallSiteList :: [([Char], SrcLoc)] -> CallStack
- getCallStack :: CallStack -> [([Char], SrcLoc)]
- pushCallStack :: ([Char], SrcLoc) -> CallStack -> CallStack
- data SrcLoc = SrcLoc {
- srcLocPackage :: [Char]
- srcLocModule :: [Char]
- srcLocFile :: [Char]
- srcLocStartLine :: Int
- srcLocStartCol :: Int
- srcLocEndLine :: Int
- srcLocEndCol :: Int
Implicit call stacks
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
EmptyCallStack | |
PushCallStack [Char] SrcLoc CallStack | |
FreezeCallStack CallStack | Freeze the stack at the given |
type HasCallStack = ?callStack :: CallStack Source #
Request a CallStack.
NOTE: The implicit parameter ?callStack :: CallStack
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.9.0.0
emptyCallStack :: CallStack Source #
The empty CallStack
.
Since: base-4.9.0.0
freezeCallStack :: CallStack -> CallStack Source #
Freeze a call-stack, preventing any further call-sites from being appended.
pushCallStack callSite (freezeCallStack callStack) = freezeCallStack callStack
Since: base-4.9.0.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
pushCallStack :: ([Char], SrcLoc) -> CallStack -> CallStack Source #
Push a call-site onto the stack.
This function has no effect on a frozen CallStack
.
Since: base-4.9.0.0
Source locations
A single location in the source code.
Since: base-4.8.1.0
SrcLoc | |
|