[Git][ghc/ghc][wip/buggymcbugfix/15185-enum-int] Add INLINABLE pragmas to Enum list producers

Vilem-Benjamin Liepelt gitlab at gitlab.haskell.org
Thu May 14 22:58:00 UTC 2020



Vilem-Benjamin Liepelt pushed to branch wip/buggymcbugfix/15185-enum-int at Glasgow Haskell Compiler / GHC


Commits:
331970da by buggymcbugfix at 2020-05-15T01:57:45+03:00
Add INLINABLE pragmas to Enum list producers

The INLINABLE pragmas ensure that we export stable (unoptimised) unfoldings in
the interface file so we can do list fusion at usage sites.

Related tickets: #15185, #8763, #18178.

- - - - -


4 changed files:

- compiler/GHC/Tc/Deriv/Generate.hs
- libraries/base/GHC/Enum.hs
- libraries/base/GHC/Word.hs
- + testsuite/tests/perf/should_run/T15185.hs


Changes:

=====================================
compiler/GHC/Tc/Deriv/Generate.hs
=====================================
@@ -588,8 +588,8 @@ gen_Enum_binds loc tycon = do
       [ succ_enum      dflags
       , pred_enum      dflags
       , to_enum        dflags
-      , enum_from      dflags
-      , enum_from_then dflags
+      , enum_from      dflags -- [0 ..]
+      , enum_from_then dflags -- [0, 1 ..]
       , from_enum      dflags
       ]
     aux_binds = listToBag $ map DerivAuxBind


=====================================
libraries/base/GHC/Enum.hs
=====================================
@@ -139,17 +139,34 @@ class  Enum a   where
     --     * @enumFromThenTo 6 8 2 :: [Int] = []@
     enumFromThenTo      :: a -> a -> a -> [a]
 
-    succ                   = toEnum . (+ 1)  . fromEnum
-    pred                   = toEnum . (subtract 1) . fromEnum
-    enumFrom x             = map toEnum [fromEnum x ..]
-    enumFromThen x y       = map toEnum [fromEnum x, fromEnum y ..]
-    enumFromTo x y         = map toEnum [fromEnum x .. fromEnum y]
+    succ = toEnum . (+ 1) . fromEnum
+
+    pred = toEnum . (subtract 1) . fromEnum
+
+    -- See Note [Stable Unfolding for list producers]
+    {-# INLINABLE enumFrom #-}
+    enumFrom x = map toEnum [fromEnum x ..]
+
+    -- See Note [Stable Unfolding for list producers]
+    {-# INLINABLE enumFromThen #-}
+    enumFromThen x y = map toEnum [fromEnum x, fromEnum y ..]
+
+    -- See Note [Stable Unfolding for list producers]
+    {-# INLINABLE enumFromTo #-}
+    enumFromTo x y = map toEnum [fromEnum x .. fromEnum y]
+
+    -- See Note [Stable Unfolding for list producers]
+    {-# INLINABLE enumFromThenTo #-}
     enumFromThenTo x1 x2 y = map toEnum [fromEnum x1, fromEnum x2 .. fromEnum y]
 
+-- See Note [Stable Unfolding for list producers]
+{-# INLINABLE boundedEnumFrom #-}
 -- Default methods for bounded enumerations
 boundedEnumFrom :: (Enum a, Bounded a) => a -> [a]
 boundedEnumFrom n = map toEnum [fromEnum n .. fromEnum (maxBound `asTypeOf` n)]
 
+-- See Note [Stable Unfolding for list producers]
+{-# INLINABLE boundedEnumFromThen #-}
 boundedEnumFromThen :: (Enum a, Bounded a) => a -> a -> [a]
 boundedEnumFromThen n1 n2
   | i_n2 >= i_n1  = map toEnum [i_n1, i_n2 .. fromEnum (maxBound `asTypeOf` n1)]
@@ -158,6 +175,16 @@ boundedEnumFromThen n1 n2
     i_n1 = fromEnum n1
     i_n2 = fromEnum n2
 
+{-
+Note [Stable Unfolding for list producers]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+The INLINABLE pragmas ensure that we export stable (unoptimised) unfoldings in
+the interface file so we can do list fusion at usage sites.
+
+Related tickets: #15185, #8763, #18178.
+-}
+
 ------------------------------------------------------------------------
 -- Helper functions
 ------------------------------------------------------------------------


=====================================
libraries/base/GHC/Word.hs
=====================================
@@ -892,10 +892,8 @@ instance Enum Word64 where
         | x <= fromIntegral (maxBound::Int)
                         = I# (word2Int# x#)
         | otherwise     = fromEnumError "Word64" x
-    enumFrom            = integralEnumFrom
-    enumFromThen        = integralEnumFromThen
-    enumFromTo          = integralEnumFromTo
-    enumFromThenTo      = integralEnumFromThenTo
+    enumFrom            = boundedEnumFrom
+    enumFromThen        = boundedEnumFromThen
 
 -- | @since 2.01
 instance Integral Word64 where


=====================================
testsuite/tests/perf/should_run/T15185.hs
=====================================
@@ -0,0 +1,25 @@
+{-# LANGUAGE TypeApplications #-}
+
+-- Ensure that we do list fusion on `foldr f z [from..to]` for various Int` and
+-- `Word` types. Related tickets: #15185, #8763.
+
+import Control.Exception (evaluate)
+import Data.Int
+import Data.Word
+
+fact :: Integral t => t -> t
+fact n = product [1..n]
+
+main :: IO ()
+main = do
+  _ <- evaluate (fact @Int 50)
+  _ <- evaluate (fact @Int64 50)
+  _ <- evaluate (fact @Int32 50)
+  _ <- evaluate (fact @Int16 50)
+  _ <- evaluate (fact @Int8 50)
+  _ <- evaluate (fact @Word 50)
+  _ <- evaluate (fact @Word64 50)
+  _ <- evaluate (fact @Word32 50)
+  _ <- evaluate (fact @Word16 50)
+  _ <- evaluate (fact @Word8 50)
+  pure ()



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/331970da5b13140892fc7e1b4f1c1fd1f94225ef

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/331970da5b13140892fc7e1b4f1c1fd1f94225ef
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200514/5e4435bd/attachment-0001.html>


More information about the ghc-commits mailing list