Skip to content

Commit

Permalink
Remove integer-gmp / ghc-bignum dependency (#371)
Browse files Browse the repository at this point in the history
  • Loading branch information
Bodigrim committed Mar 1, 2021
1 parent 5bea91e commit b639596
Show file tree
Hide file tree
Showing 2 changed files with 15 additions and 57 deletions.
60 changes: 15 additions & 45 deletions Data/ByteString/Builder/ASCII.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,8 @@
{-# LANGUAGE ScopedTypeVariables, CPP, ForeignFunctionInterface,
MagicHash, UnboxedTuples #-}
{-# OPTIONS_HADDOCK not-home #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE Trustworthy #-}

{-# OPTIONS_HADDOCK not-home #-}

-- | Copyright : (c) 2010 - 2011 Simon Meier
-- License : BSD3-style (see LICENSE)
--
Expand Down Expand Up @@ -79,29 +80,10 @@ import Data.ByteString as S
import Data.ByteString.Lazy as L
import Data.ByteString.Builder.Internal (Builder)
import qualified Data.ByteString.Builder.Prim as P
import qualified Data.ByteString.Builder.Prim.Internal as P

import Foreign


#if __GLASGOW_HASKELL__ >= 811

import GHC.Num.Integer
#define HAS_INTEGER_CONSTR 1
#define quotRemInteger integerQuotRem#

#elif defined(INTEGER_GMP)

#define HAS_INTEGER_CONSTR 1
#define IS S#

import GHC.Integer.GMP.Internals
#endif

#if HAS_INTEGER_CONSTR
import qualified Data.ByteString.Builder.Prim.Internal as P
import Foreign.C.Types
import GHC.Types (Int(..))
#endif

------------------------------------------------------------------------------
-- Decimal Encoding
Expand Down Expand Up @@ -298,14 +280,11 @@ lazyByteStringHex = P.primMapLazyByteStringFixed P.word8HexFixed
-- Fast decimal 'Integer' encoding.
------------------------------------------------------------------------------

#if HAS_INTEGER_CONSTR
-- An optimized version of the integer serialization code
-- in blaze-textual (c) 2011 MailRank, Inc. Bryan O'Sullivan
-- <bos@mailrank.com>. It is 2.5x faster on Int-sized integers and 4.5x faster
-- on larger integers.

# define PAIR(a,b) (# a,b #)

-- | Maximal power of 10 fitting into an 'Int' without using the MSB.
-- 10 ^ 9 for 32 bit ints (31 * log 2 / log 10 = 9.33)
-- 10 ^ 18 for 64 bit ints (63 * log 2 / log 10 = 18.96)
Expand All @@ -317,8 +296,8 @@ maxPow10 = toInteger $ (10 :: Int) ^ P.caseWordSize_32_64 (9 :: Int) 18

-- | Decimal encoding of an 'Integer' using the ASCII digits.
integerDec :: Integer -> Builder
integerDec (IS i#) = intDec (I# i#)
integerDec i
| i' <- fromInteger i, toInteger i' == i = intDec i'
| i < 0 = P.primFixed P.char8 '-' `mappend` go (-i)
| otherwise = go i
where
Expand All @@ -339,27 +318,27 @@ integerDec i
where
splith [] = errImpossible "splith"
splith (n:ns) =
case n `quotRemInteger` pow10 of
PAIR(q,r) | q > 0 -> q : r : splitb ns
| otherwise -> r : splitb ns
case n `quotRem` pow10 of
(q,r) | q > 0 -> q : r : splitb ns
| otherwise -> r : splitb ns

splitb [] = []
splitb (n:ns) = case n `quotRemInteger` pow10 of
PAIR(q,r) -> q : r : splitb ns
splitb (n:ns) = case n `quotRem` pow10 of
(q,r) -> q : r : splitb ns

putH :: [Integer] -> [Int]
putH [] = errImpossible "putH"
putH (n:ns) = case n `quotRemInteger` maxPow10 of
PAIR(x,y)
putH (n:ns) = case n `quotRem` maxPow10 of
(x,y)
| q > 0 -> q : r : putB ns
| otherwise -> r : putB ns
where q = fromInteger x
r = fromInteger y

putB :: [Integer] -> [Int]
putB [] = []
putB (n:ns) = case n `quotRemInteger` maxPow10 of
PAIR(q,r) -> fromInteger q : fromInteger r : putB ns
putB (n:ns) = case n `quotRem` maxPow10 of
(q,r) -> fromInteger q : fromInteger r : putB ns


foreign import ccall unsafe "static _hs_bytestring_int_dec_padded9"
Expand All @@ -373,12 +352,3 @@ intDecPadded :: P.BoundedPrim Int
intDecPadded = P.liftFixedToBounded $ P.caseWordSize_32_64
(P.fixedPrim 9 $ c_int_dec_padded9 . fromIntegral)
(P.fixedPrim 18 $ c_long_long_int_dec_padded18 . fromIntegral)

#else
-- compilers other than GHC

-- | Decimal encoding of an 'Integer' using the ASCII digits. Implemented
-- using via the 'Show' instance of 'Integer's.
integerDec :: Integer -> Builder
integerDec = string7 . show
#endif
12 changes: 0 additions & 12 deletions bytestring.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -69,10 +69,6 @@ source-repository head
type: git
location: https://github.com/haskell/bytestring

flag integer-simple
description: Use the simple integer library instead of GMP
default: False

library
build-depends: base >= 4.9 && < 5, ghc-prim, deepseq

Expand Down Expand Up @@ -123,14 +119,6 @@ library
includes: fpstring.h
install-includes: fpstring.h

-- flags for the decimal integer serialization code
if impl(ghc >= 8.11)
build-depends: ghc-bignum >= 1.0
else
if !flag(integer-simple)
cpp-options: -DINTEGER_GMP
build-depends: integer-gmp >= 0.2

test-suite prop-compiled
type: exitcode-stdio-1.0
main-is: Properties.hs
Expand Down

0 comments on commit b639596

Please sign in to comment.