[Git][ghc/ghc][master] 4 commits: Fix spelling mistakes and typos

Marge Bot gitlab at gitlab.haskell.org
Thu May 21 16:18:18 UTC 2020



 Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
3451584f by buggymcbugfix at 2020-05-21T12:18:06-04:00
Fix spelling mistakes and typos

- - - - -
b552e531 by buggymcbugfix at 2020-05-21T12:18:06-04: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.

- - - - -
e7480063 by buggymcbugfix at 2020-05-21T12:18:06-04:00
Piggyback on Enum Word methods for Word64

If we are on a 64 bit platform, we can use the efficient Enum Word
methods for the Enum Word64 instance.

- - - - -
892b0c41 by buggymcbugfix at 2020-05-21T12:18:06-04:00
Document INLINE(ABLE) pragmas that enable fusion

- - - - -


8 changed files:

- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Types/Name/Occurrence.hs
- docs/users_guide/debugging.rst
- libraries/base/GHC/Enum.hs
- libraries/base/GHC/List.hs
- libraries/base/GHC/Word.hs
- + testsuite/tests/perf/should_run/T15185.hs
- testsuite/tests/perf/should_run/all.T


Changes:

=====================================
compiler/GHC/Tc/Deriv/Generate.hs
=====================================
@@ -592,8 +592,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


=====================================
compiler/GHC/Types/Name/Occurrence.hs
=====================================
@@ -624,7 +624,7 @@ mkIPOcc             = mk_simple_deriv varName  "$i"
 mkSpecOcc           = mk_simple_deriv varName  "$s"
 mkForeignExportOcc  = mk_simple_deriv varName  "$f"
 mkRepEqOcc          = mk_simple_deriv tvName   "$r"   -- In RULES involving Coercible
-mkClassDataConOcc   = mk_simple_deriv dataName "C:"     -- Data con for a class
+mkClassDataConOcc   = mk_simple_deriv dataName "C:"   -- Data con for a class
 mkNewTyCoOcc        = mk_simple_deriv tcName   "N:"   -- Coercion for newtypes
 mkInstTyCoOcc       = mk_simple_deriv tcName   "D:"   -- Coercion for type functions
 mkEqPredCoOcc       = mk_simple_deriv tcName   "$co"


=====================================
docs/users_guide/debugging.rst
=====================================
@@ -301,7 +301,7 @@ subexpression elimination pass.
     Rules are filtered by the user provided string, a rule is kept if a prefix
     of its name matches the string.
     The pass then checks whether any of these rules could apply to
-    the program but which didn't file for some reason. For example, specifying
+    the program but which didn't fire for some reason. For example, specifying
     ``-drule-check=SPEC`` will check whether there are any applications which
     might be subject to a rule created by specialisation.
 


=====================================
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,14 @@ boundedEnumFromThen n1 n2
     i_n1 = fromEnum n1
     i_n2 = fromEnum n2
 
+{-
+Note [Stable Unfolding for list producers]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+The INLINABLE/INLINE pragmas ensure that we export stable (unoptimised)
+unfoldings in the interface file so we can do list fusion at usage sites.
+-}
+
 ------------------------------------------------------------------------
 -- Helper functions
 ------------------------------------------------------------------------
@@ -343,16 +368,20 @@ instance  Enum Char  where
     toEnum   = chr
     fromEnum = ord
 
+    -- See Note [Stable Unfolding for list producers]
     {-# INLINE enumFrom #-}
     enumFrom (C# x) = eftChar (ord# x) 0x10FFFF#
         -- Blarg: technically I guess enumFrom isn't strict!
 
+    -- See Note [Stable Unfolding for list producers]
     {-# INLINE enumFromTo #-}
     enumFromTo (C# x) (C# y) = eftChar (ord# x) (ord# y)
 
+    -- See Note [Stable Unfolding for list producers]
     {-# INLINE enumFromThen #-}
     enumFromThen (C# x1) (C# x2) = efdChar (ord# x1) (ord# x2)
 
+    -- See Note [Stable Unfolding for list producers]
     {-# INLINE enumFromThenTo #-}
     enumFromThenTo (C# x1) (C# x2) (C# y) = efdtChar (ord# x1) (ord# x2) (ord# y)
 
@@ -472,17 +501,21 @@ instance  Enum Int  where
     toEnum   x = x
     fromEnum x = x
 
+    -- See Note [Stable Unfolding for list producers]
     {-# INLINE enumFrom #-}
     enumFrom (I# x) = eftInt x maxInt#
         where !(I# maxInt#) = maxInt
         -- Blarg: technically I guess enumFrom isn't strict!
 
+    -- See Note [Stable Unfolding for list producers]
     {-# INLINE enumFromTo #-}
     enumFromTo (I# x) (I# y) = eftInt x y
 
+    -- See Note [Stable Unfolding for list producers]
     {-# INLINE enumFromThen #-}
     enumFromThen (I# x1) (I# x2) = efdInt x1 x2
 
+    -- See Note [Stable Unfolding for list producers]
     {-# INLINE enumFromThenTo #-}
     enumFromThenTo (I# x1) (I# x2) (I# y) = efdtInt x1 x2 y
 
@@ -812,13 +845,20 @@ instance  Enum Integer  where
     toEnum (I# n)        = smallInteger n
     fromEnum n           = I# (integerToInt n)
 
+    -- See Note [Stable Unfolding for list producers]
     {-# INLINE enumFrom #-}
+    enumFrom x = enumDeltaInteger x 1
+
+    -- See Note [Stable Unfolding for list producers]
     {-# INLINE enumFromThen #-}
+    enumFromThen x y = enumDeltaInteger x (y-x)
+
+    -- See Note [Stable Unfolding for list producers]
     {-# INLINE enumFromTo #-}
+    enumFromTo x lim = enumDeltaToInteger x 1 lim
+
+    -- See Note [Stable Unfolding for list producers]
     {-# INLINE enumFromThenTo #-}
-    enumFrom x             = enumDeltaInteger   x 1
-    enumFromThen x y       = enumDeltaInteger   x (y-x)
-    enumFromTo x lim       = enumDeltaToInteger x 1     lim
     enumFromThenTo x y lim = enumDeltaToInteger x (y-x) lim
 
 -- See Note [How the Enum rules work]
@@ -927,6 +967,7 @@ instance Enum Natural where
     toEnum = intToNatural
 
 #if defined(MIN_VERSION_integer_gmp)
+    -- This is the integer-gmp special case. The general case is after the endif.
     fromEnum (NatS# w)
       | i >= 0    = i
       | otherwise = errorWithoutStackTrace "fromEnum: out of Int range"
@@ -936,11 +977,13 @@ instance Enum Natural where
     fromEnum n = fromEnum (naturalToInteger n)
 
     enumFrom x        = enumDeltaNatural      x (wordToNaturalBase 1##)
+
     enumFromThen x y
       | x <= y        = enumDeltaNatural      x (y-x)
       | otherwise     = enumNegDeltaToNatural x (x-y) (wordToNaturalBase 0##)
 
     enumFromTo x lim  = enumDeltaToNatural    x (wordToNaturalBase 1##) lim
+
     enumFromThenTo x y lim
       | x <= y        = enumDeltaToNatural    x (y-x) lim
       | otherwise     = enumNegDeltaToNatural x (x-y) lim


=====================================
libraries/base/GHC/List.hs
=====================================
@@ -277,10 +277,10 @@ to list-producing functions abstracted over cons and nil. Here we call them
 FB functions because their names usually end with 'FB'. It's a good idea to
 inline FB functions because:
 
-* They are higher-order functions and therefore benefits from inlining.
+* They are higher-order functions and therefore benefit from inlining.
 
 * When the final consumer is a left fold, inlining the FB functions is the only
-  way to make arity expansion to happen. See Note [Left fold via right fold].
+  way to make arity expansion happen. See Note [Left fold via right fold].
 
 For this reason we mark all FB functions INLINE [0]. The [0] phase-specifier
 ensures that calls to FB functions can be written back to the original form


=====================================
libraries/base/GHC/Word.hs
=====================================
@@ -892,10 +892,44 @@ instance Enum Word64 where
         | x <= fromIntegral (maxBound::Int)
                         = I# (word2Int# x#)
         | otherwise     = fromEnumError "Word64" x
-    enumFrom            = integralEnumFrom
-    enumFromThen        = integralEnumFromThen
-    enumFromTo          = integralEnumFromTo
-    enumFromThenTo      = integralEnumFromThenTo
+
+#if WORD_SIZE_IN_BITS < 64
+    enumFrom       = integralEnumFrom
+    enumFromThen   = integralEnumFromThen
+    enumFromTo     = integralEnumFromTo
+    enumFromThenTo = integralEnumFromThenTo
+#else
+    -- See Note [Stable Unfolding for list producers] in GHC.Enum
+    {-# INLINABLE enumFrom #-}
+    enumFrom w
+        = map wordToWord64
+        $ enumFrom (word64ToWord w)
+
+    -- See Note [Stable Unfolding for list producers] in GHC.Enum
+    {-# INLINABLE enumFromThen #-}
+    enumFromThen w s
+        = map wordToWord64
+        $ enumFromThen (word64ToWord w) (word64ToWord s)
+
+    -- See Note [Stable Unfolding for list producers] in GHC.Enum
+    {-# INLINABLE enumFromTo #-}
+    enumFromTo w1 w2
+        = map wordToWord64
+        $ enumFromTo (word64ToWord w1) (word64ToWord w2)
+
+    -- See Note [Stable Unfolding for list producers] in GHC.Enum
+    {-# INLINABLE enumFromThenTo #-}
+    enumFromThenTo w1 s w2
+        = map wordToWord64
+        $ enumFromThenTo (word64ToWord w1) (word64ToWord s) (word64ToWord w2)
+
+word64ToWord :: Word64 -> Word
+word64ToWord (W64# w#) = (W# w#)
+
+wordToWord64 :: Word -> Word64
+wordToWord64 (W# w#) = (W64# w#)
+#endif
+
 
 -- | @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 sized `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 ()


=====================================
testsuite/tests/perf/should_run/all.T
=====================================
@@ -367,6 +367,11 @@ test('T15578',
     compile_and_run,
     ['-O2'])
 
+test('T15185',
+    [collect_stats('bytes allocated', 5), only_ways(['normal'])],
+    compile_and_run,
+    ['-O'])
+
 # Test performance of creating Uniques.
 test('UniqLoop',
      [collect_stats('bytes allocated',5),



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6890c38d4568ca444cccc47dd1a86c5e020c3521...892b0c41816fca4eeea42ca03a43aac473311837

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6890c38d4568ca444cccc47dd1a86c5e020c3521...892b0c41816fca4eeea42ca03a43aac473311837
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/20200521/612c0b55/attachment-0001.html>


More information about the ghc-commits mailing list