Skip to content
Snippets Groups Projects
Commit 1f2fff89 authored by Ben Gamari's avatar Ben Gamari Committed by Marge Bot
Browse files

testsuite: Add caf_crash testcase

parent b0d6bf2a
No related branches found
No related tags found
No related merge requests found
module A (caf, mainx, square) where
import B (idd)
caf :: Int
caf = 23423
mainx :: IO ()
mainx = do
putStrLn $ show (caf + idd)
putStrLn "Hello"
putStrLn "World"
square :: IO Int
square = do
let ss = "I'm a square"
putStrLn $ ss
return $ length ss
module B (idd) where
idd :: Int
idd = 100000242418429
module D where
import A
data MyFunc = MyFunc String (IO Int)
funcCaf :: [MyFunc]
funcCaf = [MyFunc "square" square]
f1 :: MyFunc -> String
f1 (MyFunc s _) = s
f2 :: MyFunc -> IO Int
f2 (MyFunc s d) = d
main :: IO ()
main = do
mainx
putStrLn $ show $ length funcCaf
putStrLn $ show $ f1 $ head funcCaf
yay <- f2 $ head funcCaf
print yay
test('caf_crash',
[extra_files(['A.hs', 'B.hs', 'D.hs', ]),
when(ghc_dynamic(), skip),
extra_ways(['ghci-ext']),
omit_ways(['ghci']), ],
ghci_script, ['caf_crash.script'])
:set -fobject-code
:l D.hs
:set -fbyte-code
:add *D
main
:l []
System.Mem.performGC
System.Mem.performGC
3+4
100000242441852
Hello
World
1
"square"
I'm a square
12
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