module Z.Data.Parser.Numeric
(
uint, int
, hex
, rational
, float, double
, scientific
, scientifically
, rational'
, float', double'
, scientific'
, scientifically'
, hexLoop
, decLoop
, decLoopIntegerFast
, isHexDigit
, isDigit
, floatToScientific
, doubleToScientific
) where
import Control.Applicative
import Control.Monad
import Data.Bits
import Data.Int
import qualified Data.Scientific as Sci
import Data.Word
import Foreign.Ptr (IntPtr)
import qualified Z.Data.Builder.Numeric as B
import Z.Data.Parser.Base (Parser, (<?>))
import qualified Z.Data.Parser.Base as P
import qualified Z.Data.Vector.Base as V
import qualified Z.Data.Vector.Extra as V
#define WORD64_MAX_DIGITS_LEN 18
#define PLUS 43
#define MINUS 45
#define DOT 46
#define LITTLE_E 101
#define BIG_E 69
#define C_0 48
hex :: (Integral a, Bits a) => Parser a
{-# INLINE hex #-}
{-# SPECIALIZE INLINE hex :: Parser Int #-}
{-# SPECIALIZE INLINE hex :: Parser Int64 #-}
{-# SPECIALIZE INLINE hex :: Parser Int32 #-}
{-# SPECIALIZE INLINE hex :: Parser Int16 #-}
{-# SPECIALIZE INLINE hex :: Parser Int8 #-}
{-# SPECIALIZE INLINE hex :: Parser Word #-}
{-# SPECIALIZE INLINE hex :: Parser Word64 #-}
{-# SPECIALIZE INLINE hex :: Parser Word32 #-}
{-# SPECIALIZE INLINE hex :: Parser Word16 #-}
{-# SPECIALIZE INLINE hex :: Parser Word8 #-}
{-# SPECIALIZE INLINE hex :: Parser Integer #-}
{-# SPECIALIZE INLINE hex :: Parser IntPtr #-}
hex = "Z.Data.Parser.Numeric.hex" <?> hexLoop 0 <$> P.takeWhile1 isHexDigit
hexLoop :: (Integral a, Bits a)
=> a
-> V.Bytes
-> a
{-# INLINE hexLoop #-}
hexLoop = V.foldl' step
where
step a w = a `unsafeShiftL` 4 + fromIntegral (w2iHex w)
w2iHex w
| w <= 57 = w - 48
| w <= 70 = w - 55
| w <= 102 = w - 87
isHexDigit :: Word8 -> Bool
{-# INLINE isHexDigit #-}
isHexDigit w = w - 48 <= 9 || w - 65 <= 5 || w - 97 <= 5
uint :: (Integral a) => Parser a
{-# INLINE uint #-}
{-# SPECIALIZE INLINE uint :: Parser Int #-}
{-# SPECIALIZE INLINE uint :: Parser Int64 #-}
{-# SPECIALIZE INLINE uint :: Parser Int32 #-}
{-# SPECIALIZE INLINE uint :: Parser Int16 #-}
{-# SPECIALIZE INLINE uint :: Parser Int8 #-}
{-# SPECIALIZE INLINE uint :: Parser Word #-}
{-# SPECIALIZE INLINE uint :: Parser Word64 #-}
{-# SPECIALIZE INLINE uint :: Parser Word32 #-}
{-# SPECIALIZE INLINE uint :: Parser Word16 #-}
{-# SPECIALIZE INLINE uint :: Parser Word8 #-}
{-# SPECIALIZE INLINE uint :: Parser Integer #-}
uint = "Z.Data.Parser.Numeric.uint" <?> decLoop 0 <$> P.takeWhile1 isDigit
decLoop :: Integral a
=> a
-> V.Bytes
-> a
{-# INLINE decLoop #-}
decLoop = V.foldl' step
where step a w = a * 10 + fromIntegral (w - 48)
decLoopIntegerFast :: V.Bytes -> Integer
{-# INLINE decLoopIntegerFast #-}
decLoopIntegerFast bs
| V.length bs <= WORD64_MAX_DIGITS_LEN = fromIntegral (decLoop @Word64 0 bs)
| otherwise = decLoop @Integer 0 bs
isDigit :: Word8 -> Bool
isDigit w = w - 48 <= 9
{-# INLINE isDigit #-}
int :: (Integral a) => Parser a
{-# INLINE int #-}
{-# SPECIALIZE INLINE int :: Parser Int #-}
{-# SPECIALIZE INLINE int :: Parser Int64 #-}
{-# SPECIALIZE INLINE int :: Parser Int32 #-}
{-# SPECIALIZE INLINE int :: Parser Int16 #-}
{-# SPECIALIZE INLINE int :: Parser Int8 #-}
{-# SPECIALIZE INLINE int :: Parser Word #-}
{-# SPECIALIZE INLINE int :: Parser Word64 #-}
{-# SPECIALIZE INLINE int :: Parser Word32 #-}
{-# SPECIALIZE INLINE int :: Parser Word16 #-}
{-# SPECIALIZE INLINE int :: Parser Word8 #-}
{-# SPECIALIZE INLINE int :: Parser Integer #-}
int = "Z.Data.Parser.Numeric.int" <?> do
w <- P.peek
if w == MINUS
then P.skipWord8 *> (negate <$> uint')
else if w == PLUS then P.skipWord8 *> uint' else uint'
where
uint' = decLoop 0 <$> P.takeWhile1 isDigit
rational :: (Fractional a) => Parser a
{-# INLINE rational #-}
rational = "Z.Data.Parser.Numeric.rational" <?> scientificallyInternal realToFrac
double :: Parser Double
{-# INLINE double #-}
double = "Z.Data.Parser.Numeric.double" <?> scientificallyInternal Sci.toRealFloat
float :: Parser Float
{-# INLINE float #-}
float = "Z.Data.Parser.Numeric.float" <?> scientificallyInternal Sci.toRealFloat
scientific :: Parser Sci.Scientific
{-# INLINE scientific #-}
scientific = "Z.Data.Parser.Numeric.scientific" <?> scientificallyInternal id
scientifically :: (Sci.Scientific -> a) -> Parser a
{-# INLINE scientifically #-}
scientifically h = "Z.Data.Parser.Numeric.scientifically" <?> scientificallyInternal h
scientificallyInternal :: (Sci.Scientific -> a) -> Parser a
{-# INLINE scientificallyInternal #-}
scientificallyInternal h = do
!sign <- P.peek
when (sign == PLUS || sign == MINUS) (P.skipWord8)
!intPart <- P.takeWhile1 isDigit
!sci <- (do
!fracPart <- P.word8 DOT *> P.takeWhile1 isDigit
let !ilen = V.length intPart
!flen = V.length fracPart
!base =
if ilen + flen <= WORD64_MAX_DIGITS_LEN
then fromIntegral (decLoop @Word64 (decLoop @Word64 0 intPart) fracPart)
else
let i = decLoopIntegerFast intPart
f = decLoopIntegerFast fracPart
in i * 10 ^ flen + f
parseE base flen) <|> (parseE (decLoopIntegerFast intPart) 0)
pure $! if sign /= MINUS then h sci else h (negate sci)
where
{-# INLINE parseE #-}
parseE c e =
(do _ <- P.satisfy (\w -> w == LITTLE_E || w == BIG_E)
Sci.scientific c . subtract e <$> int) <|> pure (Sci.scientific c (negate e))
rational' :: (Fractional a) => Parser a
{-# INLINE rational' #-}
rational' = "Z.Data.Parser.Numeric.rational'" <?> scientificallyInternal' realToFrac
double' :: Parser Double
{-# INLINE double' #-}
double' = "Z.Data.Parser.Numeric.double'" <?> scientificallyInternal' Sci.toRealFloat
float' :: Parser Float
{-# INLINE float' #-}
float' = "Z.Data.Parser.Numeric.float'" <?> scientificallyInternal' Sci.toRealFloat
scientific' :: Parser Sci.Scientific
{-# INLINE scientific' #-}
scientific' = "Z.Data.Parser.Numeric.scientific'" <?> scientificallyInternal' id
scientifically' :: (Sci.Scientific -> a) -> P.Parser a
{-# INLINE scientifically' #-}
scientifically' h = "Z.Data.Parser.Numeric.scientifically'" <?> scientificallyInternal' h
scientificallyInternal' :: (Sci.Scientific -> a) -> P.Parser a
{-# INLINE scientificallyInternal' #-}
scientificallyInternal' h = do
!sign <- P.peek
when (sign == MINUS) (P.skipWord8)
!intPart <- P.takeWhile1 isDigit
when (V.length intPart > 1 && V.head intPart == C_0) (P.fail' "leading zeros are not allowed")
mdot <- P.peekMaybe
!sci <- case mdot of
Just DOT -> do
!fracPart <- P.skipWord8 *> P.takeWhile1 isDigit
let !ilen = V.length intPart
!flen = V.length fracPart
!base =
if ilen + flen <= WORD64_MAX_DIGITS_LEN
then fromIntegral (decLoop @Word64 (decLoop @Word64 0 intPart) fracPart)
else
let i = decLoopIntegerFast intPart
f = decLoopIntegerFast fracPart
in i * 10 ^ flen + f
parseE base flen
_ -> parseE (decLoopIntegerFast intPart) 0
pure $! if sign /= MINUS then h sci else h (negate sci)
where
{-# INLINE parseE #-}
parseE !c !e = do
me <- P.peekMaybe
e' <- case me of
Just ec | ec == LITTLE_E || ec == BIG_E -> P.skipWord8 *> int
_ -> pure 0
pure $! Sci.scientific c (e' - e)
floatToScientific :: Float -> Sci.Scientific
{-# INLINE floatToScientific #-}
floatToScientific rf | rf < 0 = -(fromFloatingDigits (B.grisu3_sp (-rf)))
| rf == 0 = 0
| otherwise = fromFloatingDigits (B.grisu3_sp rf)
doubleToScientific :: Double -> Sci.Scientific
{-# INLINE doubleToScientific #-}
doubleToScientific rf | rf < 0 = -(fromFloatingDigits (B.grisu3 (-rf)))
| rf == 0 = 0
| otherwise = fromFloatingDigits (B.grisu3 rf)
fromFloatingDigits :: ([Int], Int) -> Sci.Scientific
{-# INLINE fromFloatingDigits #-}
fromFloatingDigits (digits, e) = go digits 0 0
where
go :: [Int] -> Int64 -> Int -> Sci.Scientific
go [] !c !n = Sci.scientific (fromIntegral c) (e - n)
go (d:ds) !c !n = go ds (c * 10 + fromIntegral d) (n + 1)