Skip to content

Commit 2d17761

Browse files
committed
Move all endianness/byte-order CPP into one module (#659)
(cherry picked from commit 161780a)
1 parent ff2b020 commit 2d17761

File tree

4 files changed

+64
-52
lines changed

4 files changed

+64
-52
lines changed

Data/ByteString/Builder/Prim/Binary.hs

Lines changed: 7 additions & 35 deletions
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,7 @@
1-
{-# LANGUAGE CPP #-}
21
{-# LANGUAGE Trustworthy #-}
32

43
{-# LANGUAGE TypeApplications #-}
54

6-
#include "MachDeps.h"
7-
#include "bytestring-cpp-macros.h"
8-
9-
105
-- | Copyright : (c) 2010-2011 Simon Meier
116
-- License : BSD3-style (see LICENSE)
127
--
@@ -61,6 +56,7 @@ module Data.ByteString.Builder.Prim.Binary (
6156

6257
import Data.ByteString.Builder.Prim.Internal
6358
import Data.ByteString.Builder.Prim.Internal.Floating
59+
import Data.ByteString.Utils.ByteOrder
6460
import Data.ByteString.Utils.UnalignedWrite
6561

6662
import Foreign
@@ -86,59 +82,35 @@ word8 = fixedPrim 1 (flip poke) -- Word8 is always aligned
8682
-- | Encoding 'Word16's in big endian format.
8783
{-# INLINE word16BE #-}
8884
word16BE :: FixedPrim Word16
89-
#ifdef WORDS_BIGENDIAN
90-
word16BE = word16Host
91-
#else
92-
word16BE = byteSwap16 >$< word16Host
93-
#endif
85+
word16BE = whenLittleEndian byteSwap16 >$< word16Host
9486

9587
-- | Encoding 'Word16's in little endian format.
9688
{-# INLINE word16LE #-}
9789
word16LE :: FixedPrim Word16
98-
#ifdef WORDS_BIGENDIAN
99-
word16LE = byteSwap16 >$< word16Host
100-
#else
101-
word16LE = word16Host
102-
#endif
90+
word16LE = whenBigEndian byteSwap16 >$< word16Host
10391

10492
-- | Encoding 'Word32's in big endian format.
10593
{-# INLINE word32BE #-}
10694
word32BE :: FixedPrim Word32
107-
#ifdef WORDS_BIGENDIAN
108-
word32BE = word32Host
109-
#else
110-
word32BE = byteSwap32 >$< word32Host
111-
#endif
95+
word32BE = whenLittleEndian byteSwap32 >$< word32Host
11296

11397
-- | Encoding 'Word32's in little endian format.
11498
{-# INLINE word32LE #-}
11599
word32LE :: FixedPrim Word32
116-
#ifdef WORDS_BIGENDIAN
117-
word32LE = byteSwap32 >$< word32Host
118-
#else
119-
word32LE = word32Host
120-
#endif
100+
word32LE = whenBigEndian byteSwap32 >$< word32Host
121101

122102
-- on a little endian machine:
123103
-- word32LE w32 = fixedPrim 4 (\w p -> poke (castPtr p) w32)
124104

125105
-- | Encoding 'Word64's in big endian format.
126106
{-# INLINE word64BE #-}
127107
word64BE :: FixedPrim Word64
128-
#ifdef WORDS_BIGENDIAN
129-
word64BE = word64Host
130-
#else
131-
word64BE = byteSwap64 >$< word64Host
132-
#endif
108+
word64BE = whenLittleEndian byteSwap64 >$< word64Host
133109

134110
-- | Encoding 'Word64's in little endian format.
135111
{-# INLINE word64LE #-}
136112
word64LE :: FixedPrim Word64
137-
#ifdef WORDS_BIGENDIAN
138-
word64LE = byteSwap64 >$< word64Host
139-
#else
140-
word64LE = word64Host
141-
#endif
113+
word64LE = whenBigEndian byteSwap64 >$< word64Host
142114

143115

144116
-- | Encode a single native machine 'Word'. The 'Word's is encoded in host order,

Data/ByteString/Builder/RealFloat/Internal.hs

Lines changed: 13 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -72,6 +72,7 @@ import Data.Bits (Bits(..), FiniteBits(..))
7272
import Data.ByteString.Internal (c2w)
7373
import Data.ByteString.Builder.Prim.Internal (BoundedPrim, boundedPrim)
7474
import Data.ByteString.Builder.RealFloat.TableGenerator
75+
import Data.ByteString.Utils.ByteOrder
7576
import Data.ByteString.Utils.UnalignedWrite
7677
#if PURE_HASKELL
7778
import qualified Data.ByteString.Internal.Pure as Pure
@@ -408,25 +409,23 @@ wrapped f (I# w) = I# (f w)
408409
#if WORD_SIZE_IN_BITS == 32
409410
-- | Packs 2 32-bit system words (hi, lo) into a Word64
410411
packWord64 :: Word# -> Word# -> Word64#
411-
packWord64 hi lo =
412-
#if defined(WORDS_BIGENDIAN)
412+
packWord64 hi lo = case hostByteOrder of
413+
BigEndian ->
413414
((wordToWord64# lo) `uncheckedShiftL64#` 32#) `or64#` (wordToWord64# hi)
414-
#else
415+
LittleEndian ->
415416
((wordToWord64# hi) `uncheckedShiftL64#` 32#) `or64#` (wordToWord64# lo)
416-
#endif
417417

418418
-- | Unpacks a Word64 into 2 32-bit words (hi, lo)
419419
unpackWord64 :: Word64# -> (# Word#, Word# #)
420-
unpackWord64 w =
421-
#if defined(WORDS_BIGENDIAN)
420+
unpackWord64 w = case hostByteOrder of
421+
BigEndian ->
422422
(# word64ToWord# w
423423
, word64ToWord# (w `uncheckedShiftRL64#` 32#)
424424
#)
425-
#else
425+
LittleEndian ->
426426
(# word64ToWord# (w `uncheckedShiftRL64#` 32#)
427427
, word64ToWord# w
428428
#)
429-
#endif
430429

431430
-- | Adds 2 Word64's with 32-bit addition and manual carrying
432431
plusWord64 :: Word64# -> Word64# -> Word64#
@@ -731,21 +730,19 @@ getWord128At (Ptr arr) (I# i) = let
731730

732731
-- | Packs 2 bytes [lsb, msb] into 16-bit word
733732
packWord16 :: Word# -> Word# -> Word#
734-
packWord16 l h =
735-
#if defined(WORDS_BIGENDIAN)
733+
packWord16 l h = case hostByteOrder of
734+
BigEndian ->
736735
(h `uncheckedShiftL#` 8#) `or#` l
737-
#else
736+
LittleEndian ->
738737
(l `uncheckedShiftL#` 8#) `or#` h
739-
#endif
740738

741739
-- | Unpacks a 16-bit word into 2 bytes [lsb, msb]
742740
unpackWord16 :: Word# -> (# Word#, Word# #)
743-
unpackWord16 w =
744-
#if defined(WORDS_BIGENDIAN)
741+
unpackWord16 w = case hostByteOrder of
742+
BigEndian ->
745743
(# w `and#` 0xff##, w `uncheckedShiftRL#` 8# #)
746-
#else
744+
LittleEndian ->
747745
(# w `uncheckedShiftRL#` 8#, w `and#` 0xff## #)
748-
#endif
749746

750747

751748
-- | Static array of 2-digit pairs 00..99 for faster ascii rendering

Data/ByteString/Utils/ByteOrder.hs

Lines changed: 42 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,42 @@
1+
{-# LANGUAGE CPP #-}
2+
3+
-- | Why does this module exist? There is "GHC.ByteOrder" in base.
4+
-- But that module is /broken/ until base-4.14/ghc-8.10, so we
5+
-- can't rely on it until we drop support for older ghcs.
6+
-- See https://gitlab.haskell.org/ghc/ghc/-/issues/20338
7+
-- and https://gitlab.haskell.org/ghc/ghc/-/issues/18445
8+
9+
#include "MachDeps.h"
10+
11+
module Data.ByteString.Utils.ByteOrder
12+
( ByteOrder(..)
13+
, hostByteOrder
14+
, whenLittleEndian
15+
, whenBigEndian
16+
) where
17+
18+
data ByteOrder
19+
= LittleEndian
20+
| BigEndian
21+
22+
hostByteOrder :: ByteOrder
23+
hostByteOrder =
24+
#ifdef WORDS_BIGENDIAN
25+
BigEndian
26+
#else
27+
LittleEndian
28+
#endif
29+
30+
-- | If the host is little-endian, applies the given function to the given arg.
31+
-- If the host is big-endian, returns the second argument unchanged.
32+
whenLittleEndian :: (a -> a) -> a -> a
33+
whenLittleEndian fun val = case hostByteOrder of
34+
LittleEndian -> fun val
35+
BigEndian -> val
36+
37+
-- | If the host is little-endian, returns the second argument unchanged.
38+
-- If the host is big-endian, applies the given function to the given arg.
39+
whenBigEndian :: (a -> a) -> a -> a
40+
whenBigEndian fun val = case hostByteOrder of
41+
LittleEndian -> val
42+
BigEndian -> fun val

bytestring.cabal

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -120,6 +120,7 @@ library
120120
Data.ByteString.Lazy.ReadNat
121121
Data.ByteString.ReadInt
122122
Data.ByteString.ReadNat
123+
Data.ByteString.Utils.ByteOrder
123124
Data.ByteString.Utils.UnalignedWrite
124125

125126
default-language: Haskell2010
@@ -140,7 +141,7 @@ library
140141
-fmax-simplifier-iterations=10
141142
-fdicts-cheap
142143
-fspec-constr-count=6
143-
144+
144145
if arch(javascript) || flag(pure-haskell)
145146
cpp-options: -DPURE_HASKELL=1
146147
other-modules: Data.ByteString.Internal.Pure

0 commit comments

Comments
 (0)