[commit: packages/binary] master: Mark INLINEs with a phase to remove warning. (112a1a5)
git at git.haskell.org
git at git.haskell.org
Wed Dec 16 09:42:49 UTC 2015
Repository : ssh://git@git.haskell.org/binary
On branch : master
Link : http://git.haskell.org/packages/binary.git/commitdiff/112a1a5d6d8069cd227d51d99a142da64f0a61aa
>---------------------------------------------------------------
commit 112a1a5d6d8069cd227d51d99a142da64f0a61aa
Author: Lennart Kolmodin <kolmodin at google.com>
Date: Thu Jul 30 18:56:51 2015 +0200
Mark INLINEs with a phase to remove warning.
The warnings are like this;
Rule "getWord16le/readN" may never fire
because ‘getWord16le’ might inline first
The RULES do the same thing as the inlining, so either one is fine.
Specifying a phase removes the warning.
>---------------------------------------------------------------
112a1a5d6d8069cd227d51d99a142da64f0a61aa
src/Data/Binary/Get.hs | 14 +++++++-------
1 file changed, 7 insertions(+), 7 deletions(-)
diff --git a/src/Data/Binary/Get.hs b/src/Data/Binary/Get.hs
index 0541efb..091a14c 100644
--- a/src/Data/Binary/Get.hs
+++ b/src/Data/Binary/Get.hs
@@ -409,7 +409,7 @@ getPtr n = readNWith n peek
-- | Read a Word8 from the monad state
getWord8 :: Get Word8
getWord8 = readN 1 B.unsafeHead
-{-# INLINE getWord8 #-}
+{-# INLINE[2] getWord8 #-}
-- force GHC to inline getWordXX
{-# RULES
@@ -429,7 +429,7 @@ word16be :: B.ByteString -> Word16
word16be = \s ->
(fromIntegral (s `B.unsafeIndex` 0) `shiftl_w16` 8) .|.
(fromIntegral (s `B.unsafeIndex` 1))
-{-# INLINE getWord16be #-}
+{-# INLINE[2] getWord16be #-}
{-# INLINE word16be #-}
-- | Read a Word16 in little endian format
@@ -440,7 +440,7 @@ word16le :: B.ByteString -> Word16
word16le = \s ->
(fromIntegral (s `B.unsafeIndex` 1) `shiftl_w16` 8) .|.
(fromIntegral (s `B.unsafeIndex` 0) )
-{-# INLINE getWord16le #-}
+{-# INLINE[2] getWord16le #-}
{-# INLINE word16le #-}
-- | Read a Word32 in big endian format
@@ -453,7 +453,7 @@ word32be = \s ->
(fromIntegral (s `B.unsafeIndex` 1) `shiftl_w32` 16) .|.
(fromIntegral (s `B.unsafeIndex` 2) `shiftl_w32` 8) .|.
(fromIntegral (s `B.unsafeIndex` 3) )
-{-# INLINE getWord32be #-}
+{-# INLINE[2] getWord32be #-}
{-# INLINE word32be #-}
-- | Read a Word32 in little endian format
@@ -466,7 +466,7 @@ word32le = \s ->
(fromIntegral (s `B.unsafeIndex` 2) `shiftl_w32` 16) .|.
(fromIntegral (s `B.unsafeIndex` 1) `shiftl_w32` 8) .|.
(fromIntegral (s `B.unsafeIndex` 0) )
-{-# INLINE getWord32le #-}
+{-# INLINE[2] getWord32le #-}
{-# INLINE word32le #-}
-- | Read a Word64 in big endian format
@@ -483,7 +483,7 @@ word64be = \s ->
(fromIntegral (s `B.unsafeIndex` 5) `shiftl_w64` 16) .|.
(fromIntegral (s `B.unsafeIndex` 6) `shiftl_w64` 8) .|.
(fromIntegral (s `B.unsafeIndex` 7) )
-{-# INLINE getWord64be #-}
+{-# INLINE[2] getWord64be #-}
{-# INLINE word64be #-}
-- | Read a Word64 in little endian format
@@ -500,7 +500,7 @@ word64le = \s ->
(fromIntegral (s `B.unsafeIndex` 2) `shiftl_w64` 16) .|.
(fromIntegral (s `B.unsafeIndex` 1) `shiftl_w64` 8) .|.
(fromIntegral (s `B.unsafeIndex` 0) )
-{-# INLINE getWord64le #-}
+{-# INLINE[2] getWord64le #-}
{-# INLINE word64le #-}
------------------------------------------------------------------------
More information about the ghc-commits
mailing list