Skip to content

Commit

Permalink
Consolidate primop compat in module
Browse files Browse the repository at this point in the history
  • Loading branch information
Ericson2314 committed Dec 1, 2020
1 parent 7d54dff commit d6a34c4
Show file tree
Hide file tree
Showing 7 changed files with 43 additions and 51 deletions.
12 changes: 1 addition & 11 deletions src/Data/Text/Array.hs
Original file line number Diff line number Diff line change
Expand Up @@ -64,6 +64,7 @@ import Control.Monad.ST.Unsafe (unsafeIOToST)
import Control.Monad.ST (unsafeIOToST)
#endif
import Data.Bits ((.&.), xor)
import Data.Text.Internal.PrimCompat ( word16ToWord#, wordToWord16# )
import Data.Text.Internal.Unsafe (inlinePerformIO)
import Data.Text.Internal.Unsafe.Shift (shiftL, shiftR)
#if MIN_VERSION_base(4,5,0)
Expand All @@ -78,17 +79,6 @@ import GHC.ST (ST(..), runST)
import GHC.Word (Word16(..))
import Prelude hiding (length, read)

#if MIN_VERSION_base(4,16,0)
import GHC.Base ( word16ToWord#, wordToWord16# )
#else
import GHC.Prim (Word#)
word16ToWord#, wordToWord16# :: Word# -> Word#
word16ToWord# w = w
wordToWord16# w = w
{-# INLINE wordToWord16# #-}
{-# INLINE word16ToWord# #-}
#endif

-- | Immutable array type.
--
-- The 'Array' constructor is exposed since @text-1.1.1.3@
Expand Down
7 changes: 1 addition & 6 deletions src/Data/Text/Internal/Encoding/Utf16.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,12 +25,7 @@ module Data.Text.Internal.Encoding.Utf16

import GHC.Word (Word16(..))
import GHC.Exts
#if !MIN_VERSION_base(4,16,0)
import GHC.Prim (Word#)
word16ToWord# :: Word# -> Word#
word16ToWord# w = w
{-# INLINE word16ToWord# #-}
#endif
import Data.Text.Internal.PrimCompat ( word16ToWord# )

chr2 :: Word16 -> Word16 -> Char
chr2 (W16# a#) (W16# b#) = C# (chr# (upper# +# lower# +# 0x10000#))
Expand Down
8 changes: 1 addition & 7 deletions src/Data/Text/Internal/Encoding/Utf8.hs
Original file line number Diff line number Diff line change
Expand Up @@ -45,13 +45,7 @@ import Data.Text.Internal.Unsafe.Char (ord)
import Data.Text.Internal.Unsafe.Shift (shiftR)
import GHC.Exts
import GHC.Word (Word8(..))

#if !MIN_VERSION_base(4,16,0)
import GHC.Prim (Word#)
word8ToWord# :: Word# -> Word#
word8ToWord# w = w
{-# INLINE word8ToWord# #-}
#endif
import Data.Text.Internal.PrimCompat ( word8ToWord# )

default(Int)

Expand Down
37 changes: 37 additions & 0 deletions src/Data/Text/Internal/PrimCompat.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,37 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}

module Data.Text.Internal.PrimCompat
( word8ToWord#
, wordToWord8#

, word16ToWord#
, wordToWord16#

, wordToWord32#
, word32ToWord#
) where

#if MIN_VERSION_base(4,16,0)

import GHC.Base

#else

import GHC.Prim (Word#)

wordToWord8#, word8ToWord# :: Word# -> Word#
wordToWord16#, word16ToWord# :: Word# -> Word#
wordToWord32#, word32ToWord# :: Word# -> Word#
word8ToWord# w = w
word16ToWord# w = w
word32ToWord# w = w
wordToWord8# w = w
wordToWord16# w = w
wordToWord32# w = w
{-# INLINE wordToWord16# #-}
{-# INLINE word16ToWord# #-}
{-# INLINE wordToWord32# #-}
{-# INLINE word32ToWord# #-}

#endif
14 changes: 1 addition & 13 deletions src/Data/Text/Internal/Unsafe/Char.hs
Original file line number Diff line number Diff line change
Expand Up @@ -35,19 +35,7 @@ import Data.Text.Internal.Unsafe.Shift (shiftR)
import GHC.Exts (Char(..), Int(..), chr#, ord#, word2Int#)
import GHC.Word (Word8(..), Word16(..), Word32(..))
import qualified Data.Text.Array as A

#if MIN_VERSION_base(4,16,0)
import GHC.Exts ( word8ToWord#, word16ToWord#, word32ToWord# )
#else
import GHC.Prim (Word#)
word8ToWord#, word16ToWord#, word32ToWord# :: Word# -> Word#
word8ToWord# w = w
word16ToWord# w = w
word32ToWord# w = w
{-# INLINE word8ToWord# #-}
{-# INLINE word16ToWord# #-}
{-# INLINE word32ToWord# #-}
#endif
import Data.Text.Internal.PrimCompat ( word8ToWord#, word16ToWord#, word32ToWord# )

ord :: Char -> Int
ord (C# c#) = I# (ord# c#)
Expand Down
15 changes: 1 addition & 14 deletions src/Data/Text/Internal/Unsafe/Shift.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,22 +21,9 @@ module Data.Text.Internal.Unsafe.Shift
) where

-- import qualified Data.Bits as Bits
import Data.Text.Internal.PrimCompat
import GHC.Word

import GHC.Base
#if !MIN_VERSION_base(4,16,0)
import GHC.Prim (Word#)
word16ToWord#, word32ToWord# :: Word# -> Word#
wordToWord16#, wordToWord32# :: Word# -> Word#
word16ToWord# w = w
word32ToWord# w = w
wordToWord16# w = w
wordToWord32# w = w
{-# INLINE wordToWord16# #-}
{-# INLINE word16ToWord# #-}
{-# INLINE wordToWord32# #-}
{-# INLINE word32ToWord# #-}
#endif

-- | This is a workaround for poor optimisation in GHC 6.8.2. It
-- fails to notice constant-width shifts, and adds a test and branch
Expand Down
1 change: 1 addition & 0 deletions text.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -121,6 +121,7 @@ library
Data.Text.Internal.Builder.Int.Digits
Data.Text.Internal.Builder.RealFloat.Functions
Data.Text.Internal.ByteStringCompat
Data.Text.Internal.PrimCompat
Data.Text.Internal.Encoding.Fusion
Data.Text.Internal.Encoding.Fusion.Common
Data.Text.Internal.Encoding.Utf16
Expand Down

0 comments on commit d6a34c4

Please sign in to comment.