{-# LANGUAGE BangPatterns #-}
module Std.Data.Parser.Numeric
(
uint, int
, hex
, rational
, float, double
, scientific
, scientifically
) where
import Control.Applicative
import Control.Monad
import Data.Bits
import Data.Int
import qualified Data.Primitive.PrimArray as A
import qualified Data.Scientific as Sci
import Data.Word
import Data.Word8 (isDigit, isHexDigit)
import Foreign.Ptr (IntPtr)
import Std.Data.Parser.Base (Parser)
import qualified Std.Data.Parser.Base as P
import qualified Std.Data.Vector.Base as V
import qualified Std.Data.Vector.Extra as V
minus, plus, littleE, bigE, dot :: Word8
minus = 45
plus = 43
littleE = 101
bigE = 69
dot = 46
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 IntPtr #-}
hex = do
(V.Vec arr s l) <- P.takeWhile1 isHexDigit
return $! hexLoop arr s (l-1) 0
where
hexLoop arr !i !j !acc
| j == 0 = acc .|. w2iHex (A.indexPrimArray arr i)
| otherwise =
let acc' = acc .|. w2iHex (A.indexPrimArray arr i) `unsafeShiftL` (j*4)
in hexLoop arr (i+1) (j-1) acc'
w2iHex :: (Integral a) => Word8 -> a
{-# INLINE w2iHex #-}
w2iHex w
| w <= 57 = fromIntegral w - 48
| 65 <= w && w <= 70 = fromIntegral w - 55
| 97 <= w && w <= 102 = fromIntegral w - 87
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 #-}
uint = do
(V.Vec arr s l) <- P.takeWhile1 isDigit
return $! decLoop arr s (l-1) 0
where
decLoop arr !i !j !acc
| j == 0 = acc*10 + w2iDec (A.indexPrimArray arr i)
| otherwise =
let acc' = acc*10 + w2iDec (A.indexPrimArray arr i)
in decLoop arr (i+1) (j-1) acc'
w2iDec :: (Integral a) => Word8 -> a
{-# INLINE w2iDec #-}
w2iDec w = fromIntegral w - 48
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 #-}
int = do
w <- P.peek
if w == minus
then P.skip 1 >> negate <$> uint
else if w == plus then P.skip 1 >> uint else uint
rational :: Fractional a => Parser a
{-# INLINE rational #-}
rational = scientifically realToFrac
double :: Parser Double
{-# INLINE double #-}
double = scientifically Sci.toRealFloat
float :: Parser Float
{-# INLINE float #-}
float = scientifically Sci.toRealFloat
scientific :: Parser Sci.Scientific
{-# INLINE scientific #-}
scientific = scientifically id
scientifically :: (Sci.Scientific -> a) -> Parser a
{-# INLINE scientifically #-}
scientifically h = do
sign <- P.peek
when (sign == plus || sign == minus) (P.skip 1)
intPart <- uint
sci <- (do (V.Vec arr s l) <- P.word8 dot >> P.takeWhile1 isDigit
let intPart' = intPart * (10 ^ l)
fracPart = decLoop arr s (l-1) 0
parseE (intPart' + fracPart) l
) <|> (parseE intPart 0)
if sign /= minus then return $! h sci else return $! h (negate sci)
where
{-# INLINE parseE #-}
parseE c e =
(do _ <- P.satisfy (\w -> w == littleE || w == bigE)
(Sci.scientific c . (subtract e) <$> int)) <|> return (Sci.scientific c (negate e))
decLoop arr !i !j !acc
| j == 0 = acc*10 + w2iDec (A.indexPrimArray arr i)
| otherwise =
let acc' = acc*10 + w2iDec (A.indexPrimArray arr i)
in decLoop arr (i+1) (j-1) acc'