Skip to content
Snippets Groups Projects
Commit db80a5cc authored by Matthew Pickering's avatar Matthew Pickering
Browse files

Add test for whereFrom#

parent 9087899e
No related branches found
No related tags found
No related merge requests found
......@@ -14,6 +14,17 @@ test('dynamic-prof2', [only_ways(['normal']), extra_run_opts('+RTS -hT --no-auto
test('dynamic-prof3', [only_ways(['normal']), extra_run_opts('+RTS -hT --no-automatic-heap-samples')], compile_and_run, [''])
test('staticcallstack001',
[ omit_ways(['ghci-ext-prof']), # produces a different stack
], compile_and_run,
['-O0 -g3 -fdistinct-constructor-tables -finfo-table-map'])
test('staticcallstack002',
[ omit_ways(['ghci-ext-prof']), # produces a different stack
], compile_and_run,
['-O0 -g3 -fdistinct-constructor-tables -finfo-table-map'])
# Below this line, run tests only with profiling ways.
setTestOpts(req_profiling)
setTestOpts(extra_ways(['prof', 'ghci-ext-prof']))
......
module Main where
import GHC.Stack.CCS
data D = D Int deriving Show
ff = id (D 5)
{-# NOINLINE ff #-}
{-# NOINLINE qq #-}
qq x = D x
caf = D 5
main = do
print . tail =<< whereFrom (D 5)
print . tail =<< whereFrom caf
print . tail =<< whereFrom (id (D 5))
["2","D","main","Main","staticcallstack001.hs:16:20-34"]
["2","D","caf","Main","staticcallstack001.hs:13:1-9"]
["15","D","main","Main","staticcallstack001.hs:18:30-39"]
{-# LANGUAGE UnboxedTuples #-}
module Main where
import GHC.Stack.CCS
-- Unboxed data constructors don't have info tables so there is
-- a special case to not generate distinct info tables for unboxed
-- constructors.
main = do
print . tail =<< whereFrom (undefined (# #))
print . tail =<< whereFrom (undefined (# () #))
print . tail =<< whereFrom (undefined (# (), () #))
print . tail =<< whereFrom (undefined (# | () #))
["15","Any","main","Main","staticcallstack002.hs:10:30-46"]
["15","Any","main","Main","staticcallstack002.hs:11:30-49"]
["15","Any","main","Main","staticcallstack002.hs:12:30-53"]
["15","Any","main","Main","staticcallstack002.hs:13:30-51"]
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment