From b758d0f1869982e2d758f1bb156f325f719eb538 Mon Sep 17 00:00:00 2001
From: simonm <unknown>
Date: Thu, 16 Oct 1997 12:17:07 +0000
Subject: [PATCH] [project @ 1997-10-16 12:17:05 by simonm] polymorphic
 recursion/space leak test

---
 ghc/tests/typecheck/should_run/tcrun002.hs     | 18 ++++++++++++++++++
 ghc/tests/typecheck/should_run/tcrun002.stdout |  1 +
 2 files changed, 19 insertions(+)
 create mode 100644 ghc/tests/typecheck/should_run/tcrun002.hs
 create mode 100644 ghc/tests/typecheck/should_run/tcrun002.stdout

diff --git a/ghc/tests/typecheck/should_run/tcrun002.hs b/ghc/tests/typecheck/should_run/tcrun002.hs
new file mode 100644
index 000000000000..79174022124d
--- /dev/null
+++ b/ghc/tests/typecheck/should_run/tcrun002.hs
@@ -0,0 +1,18 @@
+module Main where
+
+--!!! space leak from overloading !!!
+
+-- This program develops a space leak if sfoldl isn't compiled with some
+-- care.  See comment about polymorphic recursion in TcMonoBinds.lhs
+
+import System(getArgs)
+import IOBase
+import STBase
+
+sfoldl :: Eval a => (a -> Int -> a) -> a -> [Int] -> a
+sfoldl f z [] = z
+sfoldl f z (x:xs) = _scc_ "sfoldl1" (sfoldl f fzx (fzx `seq` xs))
+                  where fzx = _scc_ "fzx" (f z x)
+
+
+main = IO (\s -> case print (sfoldl (+) (0::Int) [1..200000]) of { IO a -> a s })
diff --git a/ghc/tests/typecheck/should_run/tcrun002.stdout b/ghc/tests/typecheck/should_run/tcrun002.stdout
new file mode 100644
index 000000000000..928909f8160c
--- /dev/null
+++ b/ghc/tests/typecheck/should_run/tcrun002.stdout
@@ -0,0 +1 @@
+-1474736480
-- 
GitLab