[commit: packages/binary] master: Merge branch 'master' into signed-int (7c4fe52)

git at git.haskell.org git at git.haskell.org
Tue Feb 2 21:04:28 UTC 2016


Repository : ssh://git@git.haskell.org/binary

On branch  : master
Link       : http://git.haskell.org/packages/binary.git/commitdiff/7c4fe524ff5fd4b214214ae743e3575988c0ffd2

>---------------------------------------------------------------

commit 7c4fe524ff5fd4b214214ae743e3575988c0ffd2
Merge: 03332c4 8429d6b
Author: Alexey Khudyakov <alexey.skladnoy at gmail.com>
Date:   Sun Nov 15 18:42:53 2015 +0300

    Merge branch 'master' into signed-int



>---------------------------------------------------------------

7c4fe524ff5fd4b214214ae743e3575988c0ffd2
 .gitignore                          |   2 +
 .hgignore                           |   2 +
 .travis.yml                         |  55 ++++++
 README.md                           |  53 ++---
 benchmarks/Builder.hs               |  15 +-
 benchmarks/GenericsBench.hs         |  52 +++++
 benchmarks/GenericsBenchCache.hs    |  89 +++++++++
 benchmarks/GenericsBenchTypes.hs    |  46 +++++
 benchmarks/Get.hs                   | 277 +++++++++++++++-----------
 benchmarks/Makefile                 |  34 ----
 binary.cabal                        |  79 +++++---
 changelog.md                        | 113 +++++++++++
 index.html                          | 161 ----------------
 src/Data/Binary.hs                  |   4 +
 src/Data/Binary/Builder/Base.hs     |   8 +-
 src/Data/Binary/Builder/Internal.hs |   2 +-
 src/Data/Binary/Class.hs            | 121 ++++++++++--
 src/Data/Binary/Generic.hs          |  12 +-
 src/Data/Binary/Get.hs              |  87 ++++-----
 src/Data/Binary/Get/Internal.hs     | 135 ++++++++++---
 src/Data/Binary/Put.hs              |   5 +-
 tests/Action.hs                     | 375 ++++++++++++++++++++++++++++--------
 tests/Arbitrary.hs                  |   1 +
 tests/File.hs                       |  18 +-
 tests/Makefile                      |  20 --
 tests/QC.hs                         | 131 ++++++++-----
 26 files changed, 1267 insertions(+), 630 deletions(-)

diff --cc src/Data/Binary/Get.hs
index 438fd13,de1a326..db96a97
--- a/src/Data/Binary/Get.hs
+++ b/src/Data/Binary/Get.hs
@@@ -444,14 -411,8 +430,14 @@@ getPtr n = readNWith n pee
  -- | Read a Word8 from the monad state
  getWord8 :: Get Word8
  getWord8 = readN 1 B.unsafeHead
- {-# INLINE getWord8 #-}
+ {-# INLINE[2] getWord8 #-}
  
 +-- | Read an Int8 from the monad state
 +getInt8 :: Get Int8
 +getInt8 = fromIntegral <$> getWord8
 +{-# INLINE getInt8 #-}
 +
 +
  -- force GHC to inline getWordXX
  {-# RULES
  "getWord8/readN" getWord8 = readN 1 B.unsafeHead
@@@ -542,42 -502,9 +527,42 @@@ 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 #-}
  
 +
 +-- | Read an Int16 in big endian format
 +getInt16be :: Get Int16
 +getInt16be = fromIntegral <$> getWord16be
 +{-# INLINE getInt16be #-}
 +
 +-- | Read an Int32 in big endian format
 +getInt32be :: Get Int32
 +getInt32be =  fromIntegral <$> getWord32be
 +{-# INLINE getInt32be #-}
 +
 +-- | Read an Int64 in big endian format
 +getInt64be :: Get Int64
 +getInt64be = fromIntegral <$> getWord64be
 +{-# INLINE getInt64be #-}
 +
 +
 +-- | Read an Int16 in little endian format
 +getInt16le :: Get Int16
 +getInt16le = fromIntegral <$> getWord16le
 +{-# INLINE getInt16le #-}
 +
 +-- | Read an Int32 in little endian format
 +getInt32le :: Get Int32
 +getInt32le =  fromIntegral <$> getWord32le
 +{-# INLINE getInt32le #-}
 +
 +-- | Read an Int64 in little endian format
 +getInt64le :: Get Int64
 +getInt64le = fromIntegral <$> getWord64le
 +{-# INLINE getInt64le #-}
 +
 +
  ------------------------------------------------------------------------
  -- Host-endian reads
  
diff --cc tests/QC.hs
index ff4d37c,493d2aa..414d6f9
--- a/tests/QC.hs
+++ b/tests/QC.hs
@@@ -444,12 -433,10 +473,11 @@@ tests 
              ]
  
          , testGroup "Model"
-             [ testProperty "action" Action.prop_action
-             ]
+             Action.tests
  
          , testGroup "Primitives"
 -            [ testProperty "Word16be"   (p prop_Word16be)
 +            [ testProperty "Word8"      (p prop_Word8)
 +            , testProperty "Word16be"   (p prop_Word16be)
              , testProperty "Word16le"   (p prop_Word16le)
              , testProperty "Word16host" (p prop_Word16host)
              , testProperty "Word32be"   (p prop_Word32be)



More information about the ghc-commits mailing list