Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data CallStack
- data SrcLoc = SrcLoc {
- srcLocPackage :: [Char]
- srcLocModule :: [Char]
- srcLocFile :: [Char]
- srcLocStartLine :: Int
- srcLocStartCol :: Int
- srcLocEndLine :: Int
- srcLocEndCol :: Int
- type HasCallStack = ?callStack :: CallStack
- type SrcLocPackage = String
- type SrcLocModule = String
- type SrcFun = String
- type SrcLocFile = String
- type SrcLocLine = Int
- type SrcLocCol = Int
- type CallSite = (SrcFun, SrcLoc)
- type CallSiteFilter = CallSite -> Bool
- callStack :: HasCallStack => CallStack
- getCallStack :: CallStack -> [([Char], SrcLoc)]
- fromCallSiteList :: [([Char], SrcLoc)] -> CallStack
- prettySrcLoc :: SrcLoc -> String
- prettyCallStack :: CallStack -> String
- withCallerCallStack :: HasCallStack => (CallStack -> b) -> b
- prettyCallSite :: CallSite -> String
- headCallSite :: CallStack -> Maybe CallSite
- withCurrentCallStack :: HasCallStack => (CallStack -> b) -> b
- filterCallStack :: CallSiteFilter -> CallStack -> CallStack
- overCallSites :: ([CallSite] -> [CallSite]) -> CallStack -> CallStack
- popnCallStack :: Word -> CallStack -> CallStack
- truncatedCallStack :: CallStack -> CallStack
- withNBackCallStack :: HasCallStack => Word -> (CallStack -> b) -> b
Documentation
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
Instances
Pretty CallStack Source # | |
EmbPrj CallStack Source # | |
IsList CallStack | Be aware that 'fromList . toList = id' only for unfrozen Since: base-4.9.0.0 |
Show CallStack | Since: base-4.9.0.0 |
NFData CallStack | Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
type Item CallStack | |
Defined in GHC.IsList |
A single location in the source code.
Since: base-4.8.1.0
SrcLoc | |
|
Instances
type HasCallStack = ?callStack :: CallStack #
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
type SrcLocPackage = String Source #
Type of the package name of a SrcLoc
| e.g. `Agda-2.…`
type SrcLocModule = String Source #
Type of the module name of a SrcLoc
| e.g. Foo
type SrcLocFile = String Source #
Type of a filename of a SrcLoc
| e.g. `srcfullAgdaUtilsFoo.hs`
type SrcLocLine = Int Source #
Type of a line number of a SrcLoc
type CallSiteFilter = CallSite -> Bool Source #
Type of a filter for CallSite
callStack :: HasCallStack => CallStack #
getCallStack :: CallStack -> [([Char], SrcLoc)] #
Extract a list of call-sites from the CallStack
.
The list is ordered by most recent call.
Since: base-4.8.1.0
fromCallSiteList :: [([Char], SrcLoc)] -> CallStack #
Convert a list of call-sites to a CallStack
.
Since: base-4.9.0.0
prettySrcLoc :: SrcLoc -> String #
Pretty print a SrcLoc
.
Since: base-4.9.0.0
prettyCallStack :: CallStack -> String Source #
Pretty-print a CallStack
. This has a few differences from GHC.Stack.prettyCallStackLines
.
We omit the "CallStack (from GetCallStack)" header line for brevity.
If there is only one entry (which is common, due to the manual nature of the HasCallStack
constraint),
shows the entry on one line. If there are multiple, then the following lines are indented.
withCallerCallStack :: HasCallStack => (CallStack -> b) -> b Source #
prettyCallSite :: CallSite -> String Source #
The same as the un-exported internal function in GHC.Exceptions (prettyCallStackLines)
Prints like: doFoo, called at foo.hs:190:24 in main:Main
headCallSite :: CallStack -> Maybe CallSite Source #
Get the most recent CallSite
in a CallStack
, if there is one.
withCurrentCallStack :: HasCallStack => (CallStack -> b) -> b Source #
filterCallStack :: CallSiteFilter -> CallStack -> CallStack Source #
Transform a CallStack
by filtering each CallSite
overCallSites :: ([CallSite] -> [CallSite]) -> CallStack -> CallStack Source #
Transform a CallStack
by transforming its list of CallSite
popnCallStack :: Word -> CallStack -> CallStack Source #
Pops n entries off a CallStack
using popCallStack
.
Note that frozen callstacks are unaffected.
truncatedCallStack :: CallStack -> CallStack Source #
CallStack
comprising only the most recent CallSite
withNBackCallStack :: HasCallStack => Word -> (CallStack -> b) -> b Source #