|
1
|
1
|
{-# LANGUAGE CPP #-}
|
|
|
2
|
+{-# LANGUAGE MagicHash #-}
|
|
2
|
3
|
{-# LANGUAGE UnboxedTuples #-}
|
|
3
|
4
|
{-# LANGUAGE DerivingVia #-}
|
|
4
|
5
|
|
| ... |
... |
@@ -160,14 +161,17 @@ import qualified Data.Set as Set |
|
160
|
161
|
import Data.Time
|
|
161
|
162
|
import Data.List (unfoldr)
|
|
162
|
163
|
import System.IO as IO
|
|
163
|
|
-import System.IO.Unsafe ( unsafeInterleaveIO )
|
|
164
|
164
|
import System.IO.Error ( mkIOError, eofErrorType )
|
|
165
|
165
|
import Type.Reflection ( Typeable, SomeTypeRep(..) )
|
|
166
|
166
|
import qualified Type.Reflection as Refl
|
|
167
|
167
|
import GHC.Real ( Ratio(..) )
|
|
168
|
168
|
import Data.IntMap (IntMap)
|
|
169
|
169
|
import qualified Data.IntMap as IntMap
|
|
|
170
|
+import GHC.ByteOrder
|
|
170
|
171
|
import GHC.ForeignPtr ( unsafeWithForeignPtr )
|
|
|
172
|
+import GHC.Exts
|
|
|
173
|
+import GHC.IO
|
|
|
174
|
+import GHC.Word
|
|
171
|
175
|
|
|
172
|
176
|
import Unsafe.Coerce (unsafeCoerce)
|
|
173
|
177
|
|
| ... |
... |
@@ -638,7 +642,7 @@ getPrim (ReadBinMem _ ix_r sz_r arr_r) size f = do |
|
638
|
642
|
ix <- readFastMutInt ix_r
|
|
639
|
643
|
when (ix + size > sz_r) $
|
|
640
|
644
|
ioError (mkIOError eofErrorType "Data.Binary.getPrim" Nothing Nothing)
|
|
641
|
|
- w <- unsafeWithForeignPtr arr_r $ \p -> f (p `plusPtr` ix)
|
|
|
645
|
+ !w <- unsafeWithForeignPtr arr_r $ \p -> f (p `plusPtr` ix)
|
|
642
|
646
|
-- This is safe WRT #17760 as we we guarantee that the above line doesn't
|
|
643
|
647
|
-- diverge
|
|
644
|
648
|
writeFastMutInt ix_r (ix + size)
|
| ... |
... |
@@ -651,71 +655,52 @@ getWord8 :: ReadBinHandle -> IO Word8 |
|
651
|
655
|
getWord8 h = getPrim h 1 peek
|
|
652
|
656
|
|
|
653
|
657
|
putWord16 :: WriteBinHandle -> Word16 -> IO ()
|
|
654
|
|
-putWord16 h w = putPrim h 2 (\op -> do
|
|
655
|
|
- pokeElemOff op 0 (fromIntegral (w `shiftR` 8))
|
|
656
|
|
- pokeElemOff op 1 (fromIntegral (w .&. 0xFF))
|
|
657
|
|
- )
|
|
|
658
|
+putWord16 h w = putPrim h 2 $ \(Ptr p#) ->
|
|
|
659
|
+ IO $ \s -> (# writeWord8OffAddrAsWord16# p# 0# x# s, () #)
|
|
|
660
|
+ where
|
|
|
661
|
+ !(W16# x#) = case targetByteOrder of
|
|
|
662
|
+ BigEndian -> w
|
|
|
663
|
+ LittleEndian -> byteSwap16 w
|
|
658
|
664
|
|
|
659
|
665
|
getWord16 :: ReadBinHandle -> IO Word16
|
|
660
|
|
-getWord16 h = getPrim h 2 (\op -> do
|
|
661
|
|
- w0 <- fromIntegral <$> peekElemOff op 0
|
|
662
|
|
- w1 <- fromIntegral <$> peekElemOff op 1
|
|
663
|
|
- return $! w0 `shiftL` 8 .|. w1
|
|
664
|
|
- )
|
|
|
666
|
+getWord16 h = getPrim h 2 $ \(Ptr p#) ->
|
|
|
667
|
+ IO $ \s -> case readWord8OffAddrAsWord16# p# 0# s of
|
|
|
668
|
+ (# s', w16# #) -> case targetByteOrder of
|
|
|
669
|
+ BigEndian -> (# s', W16# w16# #)
|
|
|
670
|
+ LittleEndian -> case byteSwap16 $ W16# w16# of
|
|
|
671
|
+ !w16 -> (# s', w16 #)
|
|
665
|
672
|
|
|
666
|
673
|
putWord32 :: WriteBinHandle -> Word32 -> IO ()
|
|
667
|
|
-putWord32 h w = putPrim h 4 (\op -> do
|
|
668
|
|
- pokeElemOff op 0 (fromIntegral (w `shiftR` 24))
|
|
669
|
|
- pokeElemOff op 1 (fromIntegral ((w `shiftR` 16) .&. 0xFF))
|
|
670
|
|
- pokeElemOff op 2 (fromIntegral ((w `shiftR` 8) .&. 0xFF))
|
|
671
|
|
- pokeElemOff op 3 (fromIntegral (w .&. 0xFF))
|
|
672
|
|
- )
|
|
|
674
|
+putWord32 h w = putPrim h 4 $ \(Ptr p#) ->
|
|
|
675
|
+ IO $ \s -> (# writeWord8OffAddrAsWord32# p# 0# x# s, () #)
|
|
|
676
|
+ where
|
|
|
677
|
+ !(W32# x#) = case targetByteOrder of
|
|
|
678
|
+ BigEndian -> w
|
|
|
679
|
+ LittleEndian -> byteSwap32 w
|
|
673
|
680
|
|
|
674
|
681
|
getWord32 :: ReadBinHandle -> IO Word32
|
|
675
|
|
-getWord32 h = getPrim h 4 (\op -> do
|
|
676
|
|
- w0 <- fromIntegral <$> peekElemOff op 0
|
|
677
|
|
- w1 <- fromIntegral <$> peekElemOff op 1
|
|
678
|
|
- w2 <- fromIntegral <$> peekElemOff op 2
|
|
679
|
|
- w3 <- fromIntegral <$> peekElemOff op 3
|
|
680
|
|
-
|
|
681
|
|
- return $! (w0 `shiftL` 24) .|.
|
|
682
|
|
- (w1 `shiftL` 16) .|.
|
|
683
|
|
- (w2 `shiftL` 8) .|.
|
|
684
|
|
- w3
|
|
685
|
|
- )
|
|
|
682
|
+getWord32 h = getPrim h 4 $ \(Ptr p#) ->
|
|
|
683
|
+ IO $ \s -> case readWord8OffAddrAsWord32# p# 0# s of
|
|
|
684
|
+ (# s', w32# #) -> case targetByteOrder of
|
|
|
685
|
+ BigEndian -> (# s', W32# w32# #)
|
|
|
686
|
+ LittleEndian -> case byteSwap32 $ W32# w32# of
|
|
|
687
|
+ !w32 -> (# s', w32 #)
|
|
686
|
688
|
|
|
687
|
689
|
putWord64 :: WriteBinHandle -> Word64 -> IO ()
|
|
688
|
|
-putWord64 h w = putPrim h 8 (\op -> do
|
|
689
|
|
- pokeElemOff op 0 (fromIntegral (w `shiftR` 56))
|
|
690
|
|
- pokeElemOff op 1 (fromIntegral ((w `shiftR` 48) .&. 0xFF))
|
|
691
|
|
- pokeElemOff op 2 (fromIntegral ((w `shiftR` 40) .&. 0xFF))
|
|
692
|
|
- pokeElemOff op 3 (fromIntegral ((w `shiftR` 32) .&. 0xFF))
|
|
693
|
|
- pokeElemOff op 4 (fromIntegral ((w `shiftR` 24) .&. 0xFF))
|
|
694
|
|
- pokeElemOff op 5 (fromIntegral ((w `shiftR` 16) .&. 0xFF))
|
|
695
|
|
- pokeElemOff op 6 (fromIntegral ((w `shiftR` 8) .&. 0xFF))
|
|
696
|
|
- pokeElemOff op 7 (fromIntegral (w .&. 0xFF))
|
|
697
|
|
- )
|
|
|
690
|
+putWord64 h w = putPrim h 8 $ \(Ptr p#) ->
|
|
|
691
|
+ IO $ \s -> (# writeWord8OffAddrAsWord64# p# 0# x# s, () #)
|
|
|
692
|
+ where
|
|
|
693
|
+ !(W64# x#) = case targetByteOrder of
|
|
|
694
|
+ BigEndian -> w
|
|
|
695
|
+ LittleEndian -> byteSwap64 w
|
|
698
|
696
|
|
|
699
|
697
|
getWord64 :: ReadBinHandle -> IO Word64
|
|
700
|
|
-getWord64 h = getPrim h 8 (\op -> do
|
|
701
|
|
- w0 <- fromIntegral <$> peekElemOff op 0
|
|
702
|
|
- w1 <- fromIntegral <$> peekElemOff op 1
|
|
703
|
|
- w2 <- fromIntegral <$> peekElemOff op 2
|
|
704
|
|
- w3 <- fromIntegral <$> peekElemOff op 3
|
|
705
|
|
- w4 <- fromIntegral <$> peekElemOff op 4
|
|
706
|
|
- w5 <- fromIntegral <$> peekElemOff op 5
|
|
707
|
|
- w6 <- fromIntegral <$> peekElemOff op 6
|
|
708
|
|
- w7 <- fromIntegral <$> peekElemOff op 7
|
|
709
|
|
-
|
|
710
|
|
- return $! (w0 `shiftL` 56) .|.
|
|
711
|
|
- (w1 `shiftL` 48) .|.
|
|
712
|
|
- (w2 `shiftL` 40) .|.
|
|
713
|
|
- (w3 `shiftL` 32) .|.
|
|
714
|
|
- (w4 `shiftL` 24) .|.
|
|
715
|
|
- (w5 `shiftL` 16) .|.
|
|
716
|
|
- (w6 `shiftL` 8) .|.
|
|
717
|
|
- w7
|
|
718
|
|
- )
|
|
|
698
|
+getWord64 h = getPrim h 8 $ \(Ptr p#) ->
|
|
|
699
|
+ IO $ \s -> case readWord8OffAddrAsWord64# p# 0# s of
|
|
|
700
|
+ (# s', w64# #) -> case targetByteOrder of
|
|
|
701
|
+ BigEndian -> (# s', W64# w64# #)
|
|
|
702
|
+ LittleEndian -> case byteSwap64 $ W64# w64# of
|
|
|
703
|
+ !w64 -> (# s', w64 #)
|
|
719
|
704
|
|
|
720
|
705
|
putByte :: WriteBinHandle -> Word8 -> IO ()
|
|
721
|
706
|
putByte bh !w = putWord8 bh w
|