diff --git a/testsuite/tests/simplCore/should_run/T5997.hs b/testsuite/tests/simplCore/should_run/T5997.hs new file mode 100644 index 0000000000000000000000000000000000000000..cd0f1dda8be2fb5100f06f4d7788e09d071b9f69 --- /dev/null +++ b/testsuite/tests/simplCore/should_run/T5997.hs @@ -0,0 +1,27 @@ +{-# LANGUAGE BangPatterns #-} + +module Main where + +incompleteBetaWorker :: Double -> Double +incompleteBetaWorker _ = loop 1 1 1 1 + where + -- Constants + eps = 1e-15 + -- Loop + loop :: Double -> Int -> Double -> Double -> Double + loop !psq !ns !term !betain + | done = betain' + | ns > 10000000 = betain' + | otherwise = loop psq' (ns + 1) term' betain' + where + -- New values + term' = term + betain' = betain + psq' = if ns < 0 then psq + 1 else psq + -- This condition cause stack overflow + done = db <= eps && db <= eps*betain' where db = abs term' + -- With this it loops endlessly + -- done = db <= eps * betain' where db = abs term' + +main :: IO () +main = print $ incompleteBetaWorker 0 diff --git a/testsuite/tests/simplCore/should_run/T5997.stdout b/testsuite/tests/simplCore/should_run/T5997.stdout new file mode 100644 index 0000000000000000000000000000000000000000..d3827e75a5cadb9fe4a27e1cb9b6d192e7323120 --- /dev/null +++ b/testsuite/tests/simplCore/should_run/T5997.stdout @@ -0,0 +1 @@ +1.0 diff --git a/testsuite/tests/simplCore/should_run/all.T b/testsuite/tests/simplCore/should_run/all.T index 20b25787a05fe4967f54560d77bf5376e9a6f984..210618a90a8523579561008fc19d29856b8283e5 100644 --- a/testsuite/tests/simplCore/should_run/all.T +++ b/testsuite/tests/simplCore/should_run/all.T @@ -55,3 +55,5 @@ test('T5625', [ only_ways(['normal','optasm']), exit_code(1) ], compile_and_run, test('T5587', [ only_ways(['normal','optasm']), exit_code(1) ], compile_and_run, ['']) test('T5915', only_ways(['normal','optasm']), compile_and_run, ['']) test('T5920', only_ways(['normal','optasm']), compile_and_run, ['']) +test('T5997', normal, compile_and_run, ['']) +