module Data.Picoparsec.Number (
Number(..)
, decimal
, hexadecimal
, signed
, double
, number
, rational
, scientific
) where
import Prelude hiding (length)
import Control.Applicative (pure, (*>), (<$>), (<|>))
import Control.DeepSeq (NFData(rnf))
import Control.Monad (void, when)
import Data.Monoid.Factorial (length)
import Data.Monoid.Textual (TextualMonoid, foldl_')
import Data.Bits (Bits, (.|.), shiftL)
import Data.Char (digitToInt, isDigit, isHexDigit, ord)
import Data.Data (Data)
import Data.Function (on)
import Data.Scientific (Scientific, coefficient, base10Exponent)
import qualified Data.Scientific as Sci (scientific)
import Data.Typeable (Typeable)
import GHC.Exts (inline)
import Data.Picoparsec (Parser, string)
import qualified Data.Picoparsec.Monoid.Internal as I
data Number = I !Integer
| D !Double
deriving (Typeable, Data)
instance Show Number where
show (I a) = show a
show (D a) = show a
instance NFData Number where
rnf (I _) = ()
rnf (D _) = ()
binop :: (Integer -> Integer -> a) -> (Double -> Double -> a)
-> Number -> Number -> a
binop _ d (D a) (D b) = d a b
binop i _ (I a) (I b) = i a b
binop _ d (D a) (I b) = d a (fromIntegral b)
binop _ d (I a) (D b) = d (fromIntegral a) b
instance Eq Number where
(==) = binop (==) (==)
(/=) = binop (/=) (/=)
instance Ord Number where
(<) = binop (<) (<)
(<=) = binop (<=) (<=)
(>) = binop (>) (>)
(>=) = binop (>=) (>=)
compare = binop compare compare
instance Num Number where
(+) = binop (((I$!).) . (+)) (((D$!).) . (+))
() = binop (((I$!).) . ()) (((D$!).) . ())
(*) = binop (((I$!).) . (*)) (((D$!).) . (*))
abs (I a) = I $! abs a
abs (D a) = D $! abs a
negate (I a) = I $! negate a
negate (D a) = D $! negate a
signum (I a) = I $! signum a
signum (D a) = D $! signum a
fromInteger = (I$!) . fromInteger
instance Real Number where
toRational (I a) = fromIntegral a
toRational (D a) = toRational a
instance Fractional Number where
fromRational = (D$!) . fromRational
(/) = binop (((D$!).) . (/) `on` fromIntegral)
(((D$!).) . (/))
recip (I a) = D $! recip (fromIntegral a)
recip (D a) = D $! recip a
instance RealFrac Number where
properFraction (I a) = (fromIntegral a,0)
properFraction (D a) = case properFraction a of
(i,d) -> (i,D d)
truncate (I a) = fromIntegral a
truncate (D a) = truncate a
round (I a) = fromIntegral a
round (D a) = round a
ceiling (I a) = fromIntegral a
ceiling (D a) = ceiling a
floor (I a) = fromIntegral a
floor (D a) = floor a
hexadecimal :: (TextualMonoid t, Integral a, Bits a) => Parser t a
hexadecimal = foldl_' step 0 <$> I.takeCharsWhile1 isHexDigit
where step a c = (a `shiftL` 4) .|. fromIntegral (digitToInt c)
decimal :: (TextualMonoid t, Integral a) => Parser t a
decimal = foldl_' step 0 <$> I.takeCharsWhile1 isDigit
where step a c = a * 10 + fromIntegral (digitToInt c)
signed :: (TextualMonoid t, Num a) => Parser t a -> Parser t a
signed p = (negate <$> (string "-" *> p))
<|> (string "+" *> p)
<|> p
rational :: (TextualMonoid t, Fractional a) => Parser t a
rational = inline scientifically realToFrac
double :: TextualMonoid t => Parser t Double
double = rational
number :: TextualMonoid t => Parser t Number
number = inline scientifically $ \s ->
let e = base10Exponent s
c = coefficient s
in if e >= 0
then I (c * 10 ^ e)
else D (fromInteger c / 10 ^ negate e)
scientific :: TextualMonoid t => Parser t Scientific
scientific = inline scientifically id
scientifically :: TextualMonoid t => (Scientific -> a) -> Parser t a
scientifically h = do
sign <- I.peekChar'
let !positive = sign /= '-'
when (sign == '+' || sign == '-') $
void I.anyToken
n <- decimal
let f fracDigits = Sci.scientific (foldl_' step n fracDigits)
(negate $ length fracDigits)
step a c = a * 10 + fromIntegral (ord c ord '0')
dotty <- I.peekChar
s <- case dotty of
Just '.' -> I.anyToken *> (f <$> I.takeCharsWhile isDigit)
_ -> pure (Sci.scientific n 0)
let !signedCoeff | positive = coefficient s
| otherwise = negate $ coefficient s
(I.satisfyChar (\c -> c == 'e' || c == 'E') *>
fmap (h . Sci.scientific signedCoeff . (base10Exponent s +)) (signed decimal)) <|>
return (h $ Sci.scientific signedCoeff (base10Exponent s))