Cheng Shao pushed to branch wip/fast-binary at Glasgow Haskell Compiler / GHC

Commits:

1 changed file:

Changes:

  • compiler/GHC/Utils/Binary.hs
    1 1
     
    
    2 2
     {-# LANGUAGE CPP #-}
    
    3 3
     {-# LANGUAGE GADTs #-}
    
    4
    +{-# LANGUAGE MagicHash #-}
    
    4 5
     {-# LANGUAGE UnboxedTuples #-}
    
    5 6
     {-# LANGUAGE DerivingVia #-}
    
    6 7
     {-# LANGUAGE StandaloneDeriving #-}
    
    ... ... @@ -9,6 +10,8 @@
    9 10
     -- We always optimise this, otherwise performance of a non-optimised
    
    10 11
     -- compiler is severely affected
    
    11 12
     
    
    13
    +#include <ghcautoconf.h>
    
    14
    +
    
    12 15
     --
    
    13 16
     -- (c) The University of Glasgow 2002-2006
    
    14 17
     --
    
    ... ... @@ -162,7 +165,6 @@ import qualified Data.Set as Set
    162 165
     import Data.Time
    
    163 166
     import Data.List (unfoldr)
    
    164 167
     import System.IO as IO
    
    165
    -import System.IO.Unsafe         ( unsafeInterleaveIO )
    
    166 168
     import System.IO.Error          ( mkIOError, eofErrorType )
    
    167 169
     import Type.Reflection          ( Typeable, SomeTypeRep(..) )
    
    168 170
     import qualified Type.Reflection as Refl
    
    ... ... @@ -170,6 +172,9 @@ import GHC.Real ( Ratio(..) )
    170 172
     import Data.IntMap (IntMap)
    
    171 173
     import qualified Data.IntMap as IntMap
    
    172 174
     import GHC.ForeignPtr           ( unsafeWithForeignPtr )
    
    175
    +import GHC.Exts
    
    176
    +import GHC.IO
    
    177
    +import GHC.Word
    
    173 178
     
    
    174 179
     import Unsafe.Coerce (unsafeCoerce)
    
    175 180
     
    
    ... ... @@ -653,71 +658,64 @@ getWord8 :: ReadBinHandle -> IO Word8
    653 658
     getWord8 h = getPrim h 1 peek
    
    654 659
     
    
    655 660
     putWord16 :: WriteBinHandle -> Word16 -> IO ()
    
    656
    -putWord16 h w = putPrim h 2 (\op -> do
    
    657
    -  pokeElemOff op 0 (fromIntegral (w `shiftR` 8))
    
    658
    -  pokeElemOff op 1 (fromIntegral (w .&. 0xFF))
    
    659
    -  )
    
    661
    +putWord16 h w = putPrim h 2 $ \(Ptr p#) ->
    
    662
    +  IO $ \s -> (# writeWord8OffAddrAsWord16# p# 0# x# s, () #)
    
    663
    +  where
    
    664
    +#if defined(WORDS_BIGENDIAN)
    
    665
    +    !(W16# x#) = w
    
    666
    +#else
    
    667
    +    !(W16# x#) = byteSwap16 w
    
    668
    +#endif
    
    660 669
     
    
    661 670
     getWord16 :: ReadBinHandle -> IO Word16
    
    662
    -getWord16 h = getPrim h 2 (\op -> do
    
    663
    -  w0 <- fromIntegral <$> peekElemOff op 0
    
    664
    -  w1 <- fromIntegral <$> peekElemOff op 1
    
    665
    -  return $! w0 `shiftL` 8 .|. w1
    
    666
    -  )
    
    671
    +getWord16 h = getPrim h 2 $ \(Ptr p#) ->
    
    672
    +  IO $ \s -> case readWord8OffAddrAsWord16# p# 0# s of
    
    673
    +    (# s', w16# #) ->
    
    674
    +#if defined(WORDS_BIGENDIAN)
    
    675
    +      (# s', W16# w16# #)
    
    676
    +#else
    
    677
    +      (# s', byteSwap16 $ W16# w16# #)
    
    678
    +#endif
    
    667 679
     
    
    668 680
     putWord32 :: WriteBinHandle -> Word32 -> IO ()
    
    669
    -putWord32 h w = putPrim h 4 (\op -> do
    
    670
    -  pokeElemOff op 0 (fromIntegral (w `shiftR` 24))
    
    671
    -  pokeElemOff op 1 (fromIntegral ((w `shiftR` 16) .&. 0xFF))
    
    672
    -  pokeElemOff op 2 (fromIntegral ((w `shiftR` 8) .&. 0xFF))
    
    673
    -  pokeElemOff op 3 (fromIntegral (w .&. 0xFF))
    
    674
    -  )
    
    681
    +putWord32 h w = putPrim h 4 $ \(Ptr p#) ->
    
    682
    +  IO $ \s -> (# writeWord8OffAddrAsWord32# p# 0# x# s, () #)
    
    683
    +  where
    
    684
    +#if defined(WORDS_BIGENDIAN)
    
    685
    +    !(W32# x#) = w
    
    686
    +#else
    
    687
    +    !(W32# x#) = byteSwap32 w
    
    688
    +#endif
    
    675 689
     
    
    676 690
     getWord32 :: ReadBinHandle -> IO Word32
    
    677
    -getWord32 h = getPrim h 4 (\op -> do
    
    678
    -  w0 <- fromIntegral <$> peekElemOff op 0
    
    679
    -  w1 <- fromIntegral <$> peekElemOff op 1
    
    680
    -  w2 <- fromIntegral <$> peekElemOff op 2
    
    681
    -  w3 <- fromIntegral <$> peekElemOff op 3
    
    682
    -
    
    683
    -  return $! (w0 `shiftL` 24) .|.
    
    684
    -            (w1 `shiftL` 16) .|.
    
    685
    -            (w2 `shiftL` 8)  .|.
    
    686
    -            w3
    
    687
    -  )
    
    691
    +getWord32 h = getPrim h 4 $ \(Ptr p#) ->
    
    692
    +  IO $ \s -> case readWord8OffAddrAsWord32# p# 0# s of
    
    693
    +    (# s', w32# #) ->
    
    694
    +#if defined(WORDS_BIGENDIAN)
    
    695
    +      (# s', W32# w32# #)
    
    696
    +#else
    
    697
    +      (# s', byteSwap32 $ W32# w32# #)
    
    698
    +#endif
    
    688 699
     
    
    689 700
     putWord64 :: WriteBinHandle -> Word64 -> IO ()
    
    690
    -putWord64 h w = putPrim h 8 (\op -> do
    
    691
    -  pokeElemOff op 0 (fromIntegral (w `shiftR` 56))
    
    692
    -  pokeElemOff op 1 (fromIntegral ((w `shiftR` 48) .&. 0xFF))
    
    693
    -  pokeElemOff op 2 (fromIntegral ((w `shiftR` 40) .&. 0xFF))
    
    694
    -  pokeElemOff op 3 (fromIntegral ((w `shiftR` 32) .&. 0xFF))
    
    695
    -  pokeElemOff op 4 (fromIntegral ((w `shiftR` 24) .&. 0xFF))
    
    696
    -  pokeElemOff op 5 (fromIntegral ((w `shiftR` 16) .&. 0xFF))
    
    697
    -  pokeElemOff op 6 (fromIntegral ((w `shiftR` 8) .&. 0xFF))
    
    698
    -  pokeElemOff op 7 (fromIntegral (w .&. 0xFF))
    
    699
    -  )
    
    701
    +putWord64 h w = putPrim h 8 $ \(Ptr p#) ->
    
    702
    +  IO $ \s -> (# writeWord8OffAddrAsWord64# p# 0# x# s, () #)
    
    703
    +  where
    
    704
    +#if defined(WORDS_BIGENDIAN)
    
    705
    +    !(W64# x#) = w
    
    706
    +#else
    
    707
    +    !(W64# x#) = byteSwap64 w
    
    708
    +#endif
    
    700 709
     
    
    701 710
     getWord64 :: ReadBinHandle -> IO Word64
    
    702
    -getWord64 h = getPrim h 8 (\op -> do
    
    703
    -  w0 <- fromIntegral <$> peekElemOff op 0
    
    704
    -  w1 <- fromIntegral <$> peekElemOff op 1
    
    705
    -  w2 <- fromIntegral <$> peekElemOff op 2
    
    706
    -  w3 <- fromIntegral <$> peekElemOff op 3
    
    707
    -  w4 <- fromIntegral <$> peekElemOff op 4
    
    708
    -  w5 <- fromIntegral <$> peekElemOff op 5
    
    709
    -  w6 <- fromIntegral <$> peekElemOff op 6
    
    710
    -  w7 <- fromIntegral <$> peekElemOff op 7
    
    711
    -
    
    712
    -  return $! (w0 `shiftL` 56) .|.
    
    713
    -            (w1 `shiftL` 48) .|.
    
    714
    -            (w2 `shiftL` 40) .|.
    
    715
    -            (w3 `shiftL` 32) .|.
    
    716
    -            (w4 `shiftL` 24) .|.
    
    717
    -            (w5 `shiftL` 16) .|.
    
    718
    -            (w6 `shiftL` 8)  .|.
    
    719
    -            w7
    
    720
    -  )
    
    711
    +getWord64 h = getPrim h 8 $ \(Ptr p#) ->
    
    712
    +  IO $ \s -> case readWord8OffAddrAsWord64# p# 0# s of
    
    713
    +    (# s', w64# #) ->
    
    714
    +#if defined(WORDS_BIGENDIAN)
    
    715
    +      (# s', W64# w64# #)
    
    716
    +#else
    
    717
    +      (# s', byteSwap64 $ W64# w64# #)
    
    718
    +#endif
    
    721 719
     
    
    722 720
     putByte :: WriteBinHandle -> Word8 -> IO ()
    
    723 721
     putByte bh !w = putWord8 bh w