#4321: Unexpected stack overflow prevented by superfluous type annotation
-------------------------------+--------------------------------------------
Reporter: bjpop | Owner:
Type: bug | Status: new
Priority: high | Milestone: 7.6.1
Component: Compiler | Version: 7.5
Resolution: | Keywords:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
Failure: None/Unknown | Difficulty: Unknown
Testcase: T4321 | Blockedby:
Blocking: | Related:
-------------------------------+--------------------------------------------
Comment(by simonpj):
I got part way throught fixing this before getting distracted. My partial
patch is below.
But this still doesn't quite fix
it becase the (new) trivial wrappers aren't inlined until after
specialisation
so the opportunity is missed. The solution is to be a bit more eager
about inlining in "gentle" mode (perhaps by inlining all INLINE things),
but that takes more time than I have today, so I'm capturing the state of
play here.
{{{
diff --git a/Data/List.hs b/Data/List.hs
index 9f5001f..8cecf78 100644
--- a/Data/List.hs
+++ b/Data/List.hs
@@ -1027,10 +1027,6 @@ foldl1' _ [] = errorEmptyList
"foldl1'"
--
-----------------------------------------------------------------------------
-- List sum and product
-{-# SPECIALISE sum :: [Int] -> Int #-}
-{-# SPECIALISE sum :: [Integer] -> Integer #-}
-{-# SPECIALISE product :: [Int] -> Int #-}
-{-# SPECIALISE product :: [Integer] -> Integer #-}
-- | The 'sum' function computes the sum of a finite list of numbers.
sum :: (Num a) => [a] -> a
-- | The 'product' function computes the product of a finite list of
numbers.
@@ -1039,14 +1035,27 @@ product :: (Num a) => [a] -> a
sum = foldl (+) 0
product = foldl (*) 1
#else
-sum l = sum' l 0
- where
- sum' [] a = a
- sum' (x:xs) a = sum' xs (a+x)
-product l = prod l 1
- where
- prod [] a = a
- prod (x:xs) a = prod xs (a*x)
+{-# INLINE sum #-}
+sum l = sum' l 0
+
+sum' :: (Num a) => [a] -> a -> a
+-- We want to make specialised copies of sum in calling modules
+{-# INLINABLE sum' #-}
+{-# SPECIALISE sum' :: [Int] -> Int -> Int #-}
+{-# SPECIALISE sum' :: [Integer] -> Integer -> Integer #-}
+sum' [] a = a
+sum' (x:xs) a = sum' xs (a+x)
+
+-- product is just like sum
+{-# INLINE product #-}
+product l = product' l 1
+
+product' :: (Num a) => [a] -> a -> a
+{-# INLINABLE product' #-}
+{-# SPECIALISE product' :: [Int] -> Int -> Int #-}
+{-# SPECIALISE product' :: [Integer] -> Integer -> Integer #-}
+product' [] a = a
+product' (x:xs) a = product' xs (a*x)
#endif
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4321#comment:18>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs