Skip to content

Commit 16d6b7e

Browse files
authored
Perform unaligned writes via FFI when necessary (#587)
* Perform unaligned writes via FFI when necessary * Be a bit less ignorant about the C preprocessor * Test unaligned uses of Builders a bit more * Attempt to remove Float-related unaligned accesses * fix new old-ghc stuff * todo: figure out how to get cpp to warn about this mistake * Fix CPP mistakes * Fix another stupid CPP mistake cpp-options: -Werror=undef is pulling its weight already. * Shut up cabal check about -Werror=undef * Omit conditionally-used C bindings when unused * Revert stimes-related changes * Add question about lowerTable * Revert "Omit conditionally-used C bindings when unused" This reverts commit 145cdac. * Lots of mostly Float/Double-related tweaks - Haskell unaligned write functions now live in a new module: Data.ByteString.Utils.UnalignedWrite - The word*HexFixed functions now use unaligned writes; likewise Data.ByteString.Builder.RealFloat.Internal.copyWord16. - An FFI workaround for unaligned Float/Double writes was added. - The data tables in Data.ByteString.Builder.Prim.Internal.Base16 and Data.ByteString.Builder.RealFloat.{D,F}2S now live in the new file cbits/aligned-static-hs-data.c so that we can fearlessly perform aligned reads from them. - The static Word64 data tables are now stored in host-byte-order instead of always little-endian. - Data.ByteString.Builder.RealFloat.Internal.digit_table is now a static data blob instead of a CAF. - All CPP around castFloatToWord32/castDoubleToWord64 now lives in Data.ByteString.Builder.Prim.Internal.Floating. * Update comment about locaiton of RealFloat tables * Remove useless temporary CPP guard * Re-add words "source code" in comment
1 parent 6e6b115 commit 16d6b7e

File tree

16 files changed

+1085
-907
lines changed

16 files changed

+1085
-907
lines changed

Data/ByteString/Builder/Prim/ASCII.hs

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -81,6 +81,7 @@ import Data.ByteString.Builder.Prim.Binary
8181
import Data.ByteString.Builder.Prim.Internal
8282
import Data.ByteString.Builder.Prim.Internal.Floating
8383
import Data.ByteString.Builder.Prim.Internal.Base16
84+
import Data.ByteString.Utils.UnalignedWrite
8485

8586
import Data.Char (ord)
8687

@@ -231,8 +232,9 @@ wordHex = caseWordSize_32_64
231232
-- | Encode a 'Word8' using 2 nibbles (hexadecimal digits).
232233
{-# INLINE word8HexFixed #-}
233234
word8HexFixed :: FixedPrim Word8
234-
word8HexFixed = fixedPrim 2 $
235-
\x op -> poke (castPtr op) =<< encode8_as_16h lowerTable x
235+
word8HexFixed = fixedPrim 2 $ \x op -> do
236+
enc <- encode8_as_16h lowerTable x
237+
unalignedWriteU16 enc op
236238

237239
-- | Encode a 'Word16' using 4 nibbles.
238240
{-# INLINE word16HexFixed #-}
@@ -247,6 +249,7 @@ word32HexFixed :: FixedPrim Word32
247249
word32HexFixed =
248250
(\x -> (fromIntegral $ x `shiftR` 16, fromIntegral x))
249251
>$< pairF word16HexFixed word16HexFixed
252+
250253
-- | Encode a 'Word64' using 16 nibbles.
251254
{-# INLINE word64HexFixed #-}
252255
word64HexFixed :: FixedPrim Word64

Data/ByteString/Builder/Prim/Binary.hs

Lines changed: 22 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,12 @@
11
{-# LANGUAGE CPP #-}
22
{-# LANGUAGE Trustworthy #-}
3+
4+
{-# LANGUAGE TypeApplications #-}
5+
6+
#include "MachDeps.h"
7+
#include "bytestring-cpp-macros.h"
8+
9+
310
-- | Copyright : (c) 2010-2011 Simon Meier
411
-- License : BSD3-style (see LICENSE)
512
--
@@ -54,11 +61,10 @@ module Data.ByteString.Builder.Prim.Binary (
5461

5562
import Data.ByteString.Builder.Prim.Internal
5663
import Data.ByteString.Builder.Prim.Internal.Floating
64+
import Data.ByteString.Utils.UnalignedWrite
5765

5866
import Foreign
5967

60-
#include "MachDeps.h"
61-
6268
------------------------------------------------------------------------------
6369
-- Binary encoding
6470
------------------------------------------------------------------------------
@@ -70,7 +76,7 @@ import Foreign
7076
--
7177
{-# INLINE word8 #-}
7278
word8 :: FixedPrim Word8
73-
word8 = storableToF
79+
word8 = fixedPrim 1 (flip poke) -- Word8 is always aligned
7480

7581
--
7682
-- We rely on the fromIntegral to do the right masking for us.
@@ -143,23 +149,25 @@ word64LE = word64Host
143149
--
144150
{-# INLINE wordHost #-}
145151
wordHost :: FixedPrim Word
146-
wordHost = storableToF
152+
wordHost = case finiteBitSize (0 :: Word) of
153+
32 -> fromIntegral @Word @Word32 >$< word32Host
154+
64 -> fromIntegral @Word @Word64 >$< word64Host
155+
_ -> error "Data.ByteString.Builder.Prim.Binary.wordHost: unexpected word size"
147156

148157
-- | Encoding 'Word16's in native host order and host endianness.
149158
{-# INLINE word16Host #-}
150159
word16Host :: FixedPrim Word16
151-
word16Host = storableToF
160+
word16Host = fixedPrim 2 unalignedWriteU16
152161

153162
-- | Encoding 'Word32's in native host order and host endianness.
154163
{-# INLINE word32Host #-}
155164
word32Host :: FixedPrim Word32
156-
word32Host = storableToF
165+
word32Host = fixedPrim 4 unalignedWriteU32
157166

158167
-- | Encoding 'Word64's in native host order and host endianness.
159168
{-# INLINE word64Host #-}
160169
word64Host :: FixedPrim Word64
161-
word64Host = storableToF
162-
170+
word64Host = fixedPrim 8 unalignedWriteU64
163171

164172
------------------------------------------------------------------------------
165173
-- Int encodings
@@ -215,22 +223,22 @@ int64LE = fromIntegral >$< word64LE
215223
--
216224
{-# INLINE intHost #-}
217225
intHost :: FixedPrim Int
218-
intHost = storableToF
226+
intHost = fromIntegral @Int @Word >$< wordHost
219227

220228
-- | Encoding 'Int16's in native host order and host endianness.
221229
{-# INLINE int16Host #-}
222230
int16Host :: FixedPrim Int16
223-
int16Host = storableToF
231+
int16Host = fromIntegral @Int16 @Word16 >$< word16Host
224232

225233
-- | Encoding 'Int32's in native host order and host endianness.
226234
{-# INLINE int32Host #-}
227235
int32Host :: FixedPrim Int32
228-
int32Host = storableToF
236+
int32Host = fromIntegral @Int32 @Word32 >$< word32Host
229237

230238
-- | Encoding 'Int64's in native host order and host endianness.
231239
{-# INLINE int64Host #-}
232240
int64Host :: FixedPrim Int64
233-
int64Host = storableToF
241+
int64Host = fromIntegral @Int64 @Word64 >$< word64Host
234242

235243
-- IEEE Floating Point Numbers
236244
------------------------------
@@ -261,9 +269,9 @@ doubleLE = encodeDoubleViaWord64F word64LE
261269
--
262270
{-# INLINE floatHost #-}
263271
floatHost :: FixedPrim Float
264-
floatHost = storableToF
272+
floatHost = fixedPrim (sizeOf @Float 0) unalignedWriteFloat
265273

266274
-- | Encode a 'Double' in native host order and host endianness.
267275
{-# INLINE doubleHost #-}
268276
doubleHost :: FixedPrim Double
269-
doubleHost = storableToF
277+
doubleHost = fixedPrim (sizeOf @Double 0) unalignedWriteDouble

Data/ByteString/Builder/Prim/Internal.hs

Lines changed: 2 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -73,6 +73,7 @@ import Foreign
7373
import Prelude hiding (maxBound)
7474

7575
#include "MachDeps.h"
76+
#include "bytestring-cpp-macros.h"
7677

7778
------------------------------------------------------------------------------
7879
-- Supporting infrastructure
@@ -199,13 +200,7 @@ liftFixedToBounded = toB
199200

200201
{-# INLINE CONLIKE storableToF #-}
201202
storableToF :: forall a. Storable a => FixedPrim a
202-
-- Not all architectures are forgiving of unaligned accesses; whitelist ones
203-
-- which are known not to trap (either to the kernel for emulation, or crash).
204-
#if defined(i386_HOST_ARCH) || defined(x86_64_HOST_ARCH) \
205-
|| ((defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) \
206-
&& defined(__ARM_FEATURE_UNALIGNED)) \
207-
|| defined(powerpc_HOST_ARCH) || defined(powerpc64_HOST_ARCH) \
208-
|| defined(powerpc64le_HOST_ARCH)
203+
#if HS_UNALIGNED_POKES_OK
209204
storableToF = FP (sizeOf (undefined :: a)) (\x op -> poke (castPtr op) x)
210205
#else
211206
storableToF = FP (sizeOf (undefined :: a)) $ \x op ->

Data/ByteString/Builder/Prim/Internal/Base16.hs

Lines changed: 8 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,3 @@
1-
{-# LANGUAGE Trustworthy #-}
21
{-# LANGUAGE MagicHash #-}
32
-- |
43
-- Copyright : (c) 2011 Simon Meier
@@ -22,37 +21,25 @@ module Data.ByteString.Builder.Prim.Internal.Base16 (
2221
, encode8_as_16h
2322
) where
2423

25-
import Foreign
26-
import GHC.Exts (Addr#, Ptr(..))
24+
import Foreign
25+
import Foreign.C.Types
26+
import GHC.Exts (Addr#, Ptr(..))
2727

2828
-- Creating the encoding table
2929
------------------------------
3030

3131
-- | An encoding table for Base16 encoding.
3232
data EncodingTable = EncodingTable Addr#
3333

34+
foreign import ccall "&hs_bytestring_lower_hex_table"
35+
c_lower_hex_table :: Ptr CChar
36+
3437
-- | The encoding table for hexadecimal values with lower-case characters;
3538
-- e.g., deadbeef.
3639
{-# NOINLINE lowerTable #-}
3740
lowerTable :: EncodingTable
38-
lowerTable = EncodingTable
39-
"000102030405060708090a0b0c0d0e0f\
40-
\101112131415161718191a1b1c1d1e1f\
41-
\202122232425262728292a2b2c2d2e2f\
42-
\303132333435363738393a3b3c3d3e3f\
43-
\404142434445464748494a4b4c4d4e4f\
44-
\505152535455565758595a5b5c5d5e5f\
45-
\606162636465666768696a6b6c6d6e6f\
46-
\707172737475767778797a7b7c7d7e7f\
47-
\808182838485868788898a8b8c8d8e8f\
48-
\909192939495969798999a9b9c9d9e9f\
49-
\a0a1a2a3a4a5a6a7a8a9aaabacadaeaf\
50-
\b0b1b2b3b4b5b6b7b8b9babbbcbdbebf\
51-
\c0c1c2c3c4c5c6c7c8c9cacbcccdcecf\
52-
\d0d1d2d3d4d5d6d7d8d9dadbdcdddedf\
53-
\e0e1e2e3e4e5e6e7e8e9eaebecedeeef\
54-
\f0f1f2f3f4f5f6f7f8f9fafbfcfdfeff"#
55-
41+
lowerTable = case c_lower_hex_table of
42+
Ptr p# -> EncodingTable p#
5643

5744
-- | Encode an octet as 16bit word comprising both encoded nibbles ordered
5845
-- according to the host endianness. Writing these 16bit to memory will write
Lines changed: 60 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,8 @@
1-
{-# LANGUAGE ScopedTypeVariables #-}
2-
{-# LANGUAGE Trustworthy #-}
1+
{-# LANGUAGE CPP #-}
2+
3+
#include "MachDeps.h"
4+
#include "bytestring-cpp-macros.h"
5+
36
-- |
47
-- Copyright : (c) 2010 Simon Meier
58
--
@@ -12,45 +15,74 @@
1215
-- Conversion of 'Float's and 'Double's to 'Word32's and 'Word64's.
1316
--
1417
module Data.ByteString.Builder.Prim.Internal.Floating
15-
(
16-
-- coerceFloatToWord32
17-
-- , coerceDoubleToWord64
18-
encodeFloatViaWord32F
18+
( castFloatToWord32
19+
, castDoubleToWord64
20+
, encodeFloatViaWord32F
1921
, encodeDoubleViaWord64F
2022
) where
2123

22-
import Foreign
2324
import Data.ByteString.Builder.Prim.Internal
25+
import Data.Word
26+
27+
#if HS_CAST_FLOAT_WORD_OPS_AVAILABLE
28+
import GHC.Float (castFloatToWord32, castDoubleToWord64)
29+
#else
30+
import Foreign.Marshal.Utils
31+
import Foreign.Storable
32+
import Foreign.Ptr
2433

34+
import Data.ByteString.Internal.Type (unsafeDupablePerformIO)
2535
{-
26-
We work around ticket http://ghc.haskell.org/trac/ghc/ticket/4092 using the
27-
FFI to store the Float/Double in the buffer and peek it out again from there.
36+
We work around ticket http://ghc.haskell.org/trac/ghc/ticket/4092 by
37+
storing the Float/Double in a temp buffer and peeking it out again from there.
2838
-}
2939

40+
-- | Interpret a 'Float' as a 'Word32' as if through a bit-for-bit copy.
41+
-- (fallback if not available through GHC.Float)
42+
--
43+
-- e.g
44+
--
45+
-- > showHex (castFloatToWord32 1.0) [] = "3f800000"
46+
{-# NOINLINE castFloatToWord32 #-}
47+
castFloatToWord32 :: Float -> Word32
48+
#if (SIZEOF_HSFLOAT != SIZEOF_WORD32) || (ALIGNMENT_HSFLOAT < ALIGNMENT_WORD32)
49+
#error "don't know how to cast Float to Word32"
50+
#endif
51+
castFloatToWord32 x = unsafeDupablePerformIO (with x (peek . castPtr))
3052

31-
-- | Encode a 'Float' using a 'Word32' encoding.
53+
-- | Interpret a 'Double' as a 'Word64' as if through a bit-for-bit copy.
54+
-- (fallback if not available through GHC.Float)
3255
--
33-
-- PRE: The 'Word32' encoding must have a size of at least 4 bytes.
56+
-- e.g
57+
--
58+
-- > showHex (castDoubleToWord64 1.0) [] = "3ff0000000000000"
59+
{-# NOINLINE castDoubleToWord64 #-}
60+
castDoubleToWord64 :: Double -> Word64
61+
#if (SIZEOF_HSDOUBLE != SIZEOF_WORD64) || (ALIGNMENT_HSDOUBLE < ALIGNMENT_WORD64)
62+
#error "don't know how to cast Double to Word64"
63+
#endif
64+
castDoubleToWord64 x = unsafeDupablePerformIO (with x (peek . castPtr))
65+
#endif
66+
67+
68+
-- | Encode a 'Float' using a 'Word32' encoding.
3469
{-# INLINE encodeFloatViaWord32F #-}
3570
encodeFloatViaWord32F :: FixedPrim Word32 -> FixedPrim Float
36-
encodeFloatViaWord32F w32fe
37-
| size w32fe < sizeOf (undefined :: Float) =
38-
error "encodeFloatViaWord32F: encoding not wide enough"
39-
| otherwise = fixedPrim (size w32fe) $ \x op -> do
40-
poke (castPtr op) x
41-
x' <- peek (castPtr op)
42-
runF w32fe x' op
71+
#if HS_CAST_FLOAT_WORD_OPS_AVAILABLE
72+
encodeFloatViaWord32F = (castFloatToWord32 >$<)
73+
#else
74+
encodeFloatViaWord32F w32fe = fixedPrim (size w32fe) $ \x op -> do
75+
x' <- with x (peek . castPtr)
76+
runF w32fe x' op
77+
#endif
4378

4479
-- | Encode a 'Double' using a 'Word64' encoding.
45-
--
46-
-- PRE: The 'Word64' encoding must have a size of at least 8 bytes.
4780
{-# INLINE encodeDoubleViaWord64F #-}
4881
encodeDoubleViaWord64F :: FixedPrim Word64 -> FixedPrim Double
49-
encodeDoubleViaWord64F w64fe
50-
| size w64fe < sizeOf (undefined :: Float) =
51-
error "encodeDoubleViaWord64F: encoding not wide enough"
52-
| otherwise = fixedPrim (size w64fe) $ \x op -> do
53-
poke (castPtr op) x
54-
x' <- peek (castPtr op)
55-
runF w64fe x' op
56-
82+
#if HS_CAST_FLOAT_WORD_OPS_AVAILABLE
83+
encodeDoubleViaWord64F = (castDoubleToWord64 >$<)
84+
#else
85+
encodeDoubleViaWord64F w64fe = fixedPrim (size w64fe) $ \x op -> do
86+
x' <- with x (peek . castPtr)
87+
runF w64fe x' op
88+
#endif

0 commit comments

Comments
 (0)