
#14387: listToMaybe doesn't participate in foldr/build fusion -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.2.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by duog: Old description:
I noticed that `Data.OldList.findIndex` seems to use more memory than necessary, and that changing the definition of `listToMaybe` to be in terms of `foldr` fixed the situation.
Consider the following module: {{{ {-# LANGUAGE MagicHash #-} {-# OPTIONS_GHC -ddump-to-file -ddump-prep -O #-}
module FindIndex where
import GHC.Base (Int(I#), build) import GHC.Prim
-- | The definitions of listToMaybe, findIndices and findIndex are taken from base listToMaybe :: [a] -> Maybe a listToMaybe [] = Nothing listToMaybe (a:_) = Just a
findIndices :: (a -> Bool) -> [a] -> [Int] findIndices p ls = build $ \c n -> let go x r k | p x = I# k `c` r (k +# 1#) | otherwise = r (k +# 1#) in foldr go (\_ -> n) ls 0# {-# inline findIndices #-}
findIndex :: (a -> Bool) -> [a] -> Maybe Int findIndex p = listToMaybe . findIndices p
-- This is the definition of findIndices when USE_REPORT_PRELUDE is defined findIndices' :: (a -> Bool) -> [a] -> [Int] findIndices' p xs = [ i | (x,i) <- zip xs [0..], p x] {-# inline findIndices' #-}
listToMaybe' :: [a] -> Maybe a listToMaybe' = foldr (const . Just) Nothing
-- | using listToMaybe', we get a join point findIndex2 :: (a -> Bool) -> [a] -> Maybe Int findIndex2 p = listToMaybe' . findIndices p
-- | a "manual" implementaiton, we get a join point findIndex3 :: (a -> Bool) -> [a] -> Maybe Int findIndex3 p = go . zip [0..] where go [] = Nothing go ((i, x) : xs) | p x = Just i | otherwise = go xs
-- | alternate version of findIndices, stock listToMaybe, no join point findIndex4 :: (a -> Bool) -> [a] -> Maybe Int findIndex4 p = listToMaybe . findIndices' p
-- | alternate version of findIndices, foldr listToMaybe, we get a join point findIndex5 :: (a -> Bool) -> [a] -> Maybe Int findIndex5 p = listToMaybe' . findIndices' p }}}
Find attached .dump-prep files with ghc-8.2.1 and ghc-head at commit 5c178012f47420b5dfa417be21146ca82959d273.
My interpretation of this is: with both ghc-8.2.1 and ghc-head, findIndex{2,4,5} get join points and findIndex{"",3} don't. Having a join point means constant stack space, not having a join point means linear stack space.
I don't understand the simplifier well enough to know whether ghc could do better here, but it seems that changing the definition of `listToMaybe` to {{{ listToMaybe :: [a] -> Maybe a listToMaybe = foldr (const . Just) Nothing }}} would be a win. Are there any downsides?
New description: I noticed that `Data.OldList.findIndex` seems to use more memory than necessary, and that changing the definition of `listToMaybe` to be in terms of `foldr` fixed the situation. Consider the following module: {{{ {-# LANGUAGE MagicHash #-} {-# OPTIONS_GHC -ddump-to-file -ddump-prep -O #-} module FindIndex where import GHC.Base (Int(I#), build) import GHC.Prim -- | The definitions of listToMaybe, findIndices and findIndex are taken from base listToMaybe :: [a] -> Maybe a listToMaybe [] = Nothing listToMaybe (a:_) = Just a findIndices :: (a -> Bool) -> [a] -> [Int] findIndices p ls = build $ \c n -> let go x r k | p x = I# k `c` r (k +# 1#) | otherwise = r (k +# 1#) in foldr go (\_ -> n) ls 0# {-# inline findIndices #-} findIndex :: (a -> Bool) -> [a] -> Maybe Int findIndex p = listToMaybe . findIndices p -- This is the definition of findIndices when USE_REPORT_PRELUDE is defined findIndices' :: (a -> Bool) -> [a] -> [Int] findIndices' p xs = [ i | (x,i) <- zip xs [0..], p x] {-# inline findIndices' #-} listToMaybe' :: [a] -> Maybe a listToMaybe' = foldr (const . Just) Nothing -- | using listToMaybe', we get a join point findIndex2 :: (a -> Bool) -> [a] -> Maybe Int findIndex2 p = listToMaybe' . findIndices p -- | a "manual" implementaiton, we get a join point findIndex3 :: (a -> Bool) -> [a] -> Maybe Int findIndex3 p = go . zip [0..] where go [] = Nothing go ((i, x) : xs) | p x = Just i | otherwise = go xs -- | alternate version of findIndices, stock listToMaybe, no join point findIndex4 :: (a -> Bool) -> [a] -> Maybe Int findIndex4 p = listToMaybe . findIndices' p -- | alternate version of findIndices, foldr listToMaybe, we get a join point findIndex5 :: (a -> Bool) -> [a] -> Maybe Int findIndex5 p = listToMaybe' . findIndices' p }}} Find attached .dump-prep files with ghc-8.2.1 and ghc-head at commit 8843a39b3c941b1908a8d839f52bc323f3b45081. My interpretation of this is: with both ghc-8.2.1 and ghc-head, findIndex{2,4,5} get join points and findIndex{"",3} don't. Having a join point means constant stack space, not having a join point means linear stack space. I don't understand the simplifier well enough to know whether ghc could do better here, but it seems that changing the definition of `listToMaybe` to {{{ listToMaybe :: [a] -> Maybe a listToMaybe = foldr (const . Just) Nothing }}} would be a win. Are there any downsides? -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14387#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler