{-# OPTIONS_GHC -Wall -fwarn-tabs #-}
{-# LANGUAGE BangPatterns, ScopedTypeVariables #-}
module Data.ByteString.Lex.Fractional
(
readSigned
, readDecimal
, readHexadecimal
, readOctal
, readExponential
, decimalPrecision
, readDecimalLimited
, readExponentialLimited
) where
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Unsafe as BSU
import Data.Word (Word8)
import qualified Data.ByteString.Lex.Integral as I
import Data.ByteString.Lex.Integral (readSigned)
import Data.ByteString.Lex.Internal
justPair :: a -> b -> Maybe (a,b)
{-# INLINE justPair #-}
justPair :: a -> b -> Maybe (a, b)
justPair !a
x !b
y = (a, b) -> Maybe (a, b)
forall a. a -> Maybe a
Just (a
x,b
y)
pair :: a -> b -> (a,b)
{-# INLINE pair #-}
pair :: a -> b -> (a, b)
pair !a
x !b
y = (a
x,b
y)
readDecimal :: (Fractional a) => ByteString -> Maybe (a, ByteString)
{-# SPECIALIZE readDecimal ::
ByteString -> Maybe (Float, ByteString),
ByteString -> Maybe (Double, ByteString),
ByteString -> Maybe (Rational, ByteString) #-}
readDecimal :: ByteString -> Maybe (a, ByteString)
readDecimal ByteString
xs =
case ByteString -> Maybe (Integer, ByteString)
forall a. Integral a => ByteString -> Maybe (a, ByteString)
I.readDecimal ByteString
xs of
Maybe (Integer, ByteString)
Nothing -> Maybe (a, ByteString)
forall a. Maybe a
Nothing
Just (Integer
whole, ByteString
ys) ->
case ByteString -> Maybe (Word8, ByteString)
BS.uncons ByteString
ys of
Maybe (Word8, ByteString)
Nothing -> a -> ByteString -> Maybe (a, ByteString)
forall a b. a -> b -> Maybe (a, b)
justPair (Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
whole) ByteString
BS.empty
Just (Word8
y0,ByteString
ys0)
| Word8 -> Bool
isNotPeriod Word8
y0 -> a -> ByteString -> Maybe (a, ByteString)
forall a b. a -> b -> Maybe (a, b)
justPair (Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
whole) ByteString
ys
| Bool
otherwise ->
case ByteString -> Maybe (Integer, ByteString)
forall a. Integral a => ByteString -> Maybe (a, ByteString)
I.readDecimal ByteString
ys0 of
Maybe (Integer, ByteString)
Nothing -> a -> ByteString -> Maybe (a, ByteString)
forall a b. a -> b -> Maybe (a, b)
justPair (Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
whole) ByteString
ys
Just (Integer
part, ByteString
zs) ->
let base :: a
base = a
10 a -> Int -> a
forall a b. (Num a, Integral b) => a -> b -> a
^ (ByteString -> Int
BS.length ByteString
ys Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
BS.length ByteString
zs)
frac :: a
frac = Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
whole a -> a -> a
forall a. Num a => a -> a -> a
+ (Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
part a -> a -> a
forall a. Fractional a => a -> a -> a
/ a
base)
in a -> ByteString -> Maybe (a, ByteString)
forall a b. a -> b -> Maybe (a, b)
justPair a
frac ByteString
zs
readHexadecimal :: (Fractional a) => ByteString -> Maybe (a, ByteString)
{-# SPECIALIZE readHexadecimal ::
ByteString -> Maybe (Float, ByteString),
ByteString -> Maybe (Double, ByteString),
ByteString -> Maybe (Rational, ByteString) #-}
readHexadecimal :: ByteString -> Maybe (a, ByteString)
readHexadecimal ByteString
xs =
case ByteString -> Maybe (Integer, ByteString)
forall a. Integral a => ByteString -> Maybe (a, ByteString)
I.readHexadecimal ByteString
xs of
Maybe (Integer, ByteString)
Nothing -> Maybe (a, ByteString)
forall a. Maybe a
Nothing
Just (Integer
n, ByteString
xs') -> a -> ByteString -> Maybe (a, ByteString)
forall a b. a -> b -> Maybe (a, b)
justPair (Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
n) ByteString
xs'
readOctal :: (Fractional a) => ByteString -> Maybe (a, ByteString)
{-# SPECIALIZE readOctal ::
ByteString -> Maybe (Float, ByteString),
ByteString -> Maybe (Double, ByteString),
ByteString -> Maybe (Rational, ByteString) #-}
readOctal :: ByteString -> Maybe (a, ByteString)
readOctal ByteString
xs =
case ByteString -> Maybe (Integer, ByteString)
forall a. Integral a => ByteString -> Maybe (a, ByteString)
I.readOctal ByteString
xs of
Maybe (Integer, ByteString)
Nothing -> Maybe (a, ByteString)
forall a. Maybe a
Nothing
Just (Integer
n, ByteString
xs') -> a -> ByteString -> Maybe (a, ByteString)
forall a b. a -> b -> Maybe (a, b)
justPair (Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
n) ByteString
xs'
readExponential :: (Fractional a) => ByteString -> Maybe (a, ByteString)
{-# SPECIALIZE readExponential ::
ByteString -> Maybe (Float, ByteString),
ByteString -> Maybe (Double, ByteString),
ByteString -> Maybe (Rational, ByteString) #-}
readExponential :: ByteString -> Maybe (a, ByteString)
readExponential ByteString
xs =
case ByteString -> Maybe (a, ByteString)
forall a. Fractional a => ByteString -> Maybe (a, ByteString)
readDecimal ByteString
xs of
Maybe (a, ByteString)
Nothing -> Maybe (a, ByteString)
forall a. Maybe a
Nothing
Just (a
frac, ByteString
ys) ->
case ByteString -> Maybe (Word8, ByteString)
BS.uncons ByteString
ys of
Maybe (Word8, ByteString)
Nothing -> a -> ByteString -> Maybe (a, ByteString)
forall a b. a -> b -> Maybe (a, b)
justPair a
frac ByteString
BS.empty
Just (Word8
y0,ByteString
ys0)
| Word8 -> Bool
isNotE Word8
y0 -> a -> ByteString -> Maybe (a, ByteString)
forall a b. a -> b -> Maybe (a, b)
justPair a
frac ByteString
ys
| Bool
otherwise ->
case (ByteString -> Maybe (Int, ByteString))
-> ByteString -> Maybe (Int, ByteString)
forall a.
Num a =>
(ByteString -> Maybe (a, ByteString))
-> ByteString -> Maybe (a, ByteString)
readSigned ByteString -> Maybe (Int, ByteString)
forall a. Integral a => ByteString -> Maybe (a, ByteString)
I.readDecimal ByteString
ys0 of
Maybe (Int, ByteString)
Nothing -> a -> ByteString -> Maybe (a, ByteString)
forall a b. a -> b -> Maybe (a, b)
justPair a
frac ByteString
ys
Just (Int
ex,ByteString
zs) -> a -> ByteString -> Maybe (a, ByteString)
forall a b. a -> b -> Maybe (a, b)
justPair (a
frac a -> a -> a
forall a. Num a => a -> a -> a
* (a
10 a -> Int -> a
forall a b. (Fractional a, Integral b) => a -> b -> a
^^ (Int
ex::Int))) ByteString
zs
data DecimalFraction a = DF !Integer {-# UNPACK #-}!Int
fractionDF :: Integer -> Int -> Integer -> DecimalFraction a
{-# INLINE fractionDF #-}
fractionDF :: Integer -> Int -> Integer -> DecimalFraction a
fractionDF Integer
whole Int
scale Integer
part =
Integer -> Int -> DecimalFraction a
forall a. Integer -> Int -> DecimalFraction a
DF (Integer
whole Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* (Integer
10 Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ Int
scale) Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
part) (Int -> Int
forall a. Num a => a -> a
negate Int
scale)
fromDF :: Fractional a => DecimalFraction a -> a
{-# INLINE fromDF #-}
fromDF :: DecimalFraction a -> a
fromDF (DF Integer
frac Int
scale)
| Integer
frac Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
0 = a
0
| Int
scale Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
forall a. Bounded a => a
minBound = Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
frac a -> a -> a
forall a. Num a => a -> a -> a
* (a
10 a -> Integer -> a
forall a b. (Fractional a, Integral b) => a -> b -> a
^^ Int -> Integer
forall a. Integral a => a -> Integer
toInteger Int
scale)
| Bool
otherwise = Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
frac a -> a -> a
forall a. Num a => a -> a -> a
* (a
10 a -> Int -> a
forall a b. (Fractional a, Integral b) => a -> b -> a
^^ Int
scale)
scaleDF :: DecimalFraction a -> Int -> DecimalFraction a
{-# INLINE scaleDF #-}
scaleDF :: DecimalFraction a -> Int -> DecimalFraction a
scaleDF (DF Integer
frac Int
scale) Int
scale' = Integer -> Int -> DecimalFraction a
forall a. Integer -> Int -> DecimalFraction a
DF Integer
frac (Int
scale Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
scale')
decimalPrecision :: forall proxy a. RealFloat a => proxy a -> Int
{-# INLINE decimalPrecision #-}
decimalPrecision :: proxy a -> Int
decimalPrecision =
let proxy :: a
proxy = a
forall a. HasCallStack => a
undefined :: a
n :: Int
n = Integer -> Int
forall a. Integral a => a -> Int
numDecimalDigits (a -> Integer
forall a. RealFloat a => a -> Integer
floatRadix a
proxy Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ a -> Int
forall a. RealFloat a => a -> Int
floatDigits a
proxy)
in Int
n Int -> (proxy a -> Int) -> proxy a -> Int
`seq` \proxy a
_ -> Int
n
lengthDropWhile :: (Word8 -> Bool) -> ByteString -> (Int, ByteString)
{-# INLINE lengthDropWhile #-}
lengthDropWhile :: (Word8 -> Bool) -> ByteString -> (Int, ByteString)
lengthDropWhile Word8 -> Bool
p ByteString
xs =
let ys :: ByteString
ys = (Word8 -> Bool) -> ByteString -> ByteString
BS.dropWhile Word8 -> Bool
p ByteString
xs
in (ByteString -> Int
BS.length ByteString
xs Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
BS.length ByteString
ys, ByteString
ys)
readDecimalLimited :: (Fractional a) => Int -> ByteString -> Maybe (a, ByteString)
{-# INLINE readDecimalLimited #-}
readDecimalLimited :: Int -> ByteString -> Maybe (a, ByteString)
readDecimalLimited Int
p ByteString
xs =
case Int -> ByteString -> Maybe (DecimalFraction a, ByteString)
forall a.
Fractional a =>
Int -> ByteString -> Maybe (DecimalFraction a, ByteString)
readDecimalLimited_ Int
p ByteString
xs of
Maybe (DecimalFraction a, ByteString)
Nothing -> Maybe (a, ByteString)
forall a. Maybe a
Nothing
Just (DecimalFraction a
df,ByteString
ys) -> a -> ByteString -> Maybe (a, ByteString)
forall a b. a -> b -> Maybe (a, b)
justPair (DecimalFraction a -> a
forall a. Fractional a => DecimalFraction a -> a
fromDF DecimalFraction a
df) ByteString
ys
readDecimalLimited_ :: (Fractional a) => Int -> ByteString -> Maybe (DecimalFraction a, ByteString)
{-# SPECIALIZE readDecimalLimited_ ::
Int -> ByteString -> Maybe (DecimalFraction Float, ByteString),
Int -> ByteString -> Maybe (DecimalFraction Double, ByteString),
Int -> ByteString -> Maybe (DecimalFraction Rational, ByteString) #-}
readDecimalLimited_ :: Int -> ByteString -> Maybe (DecimalFraction a, ByteString)
readDecimalLimited_ = Int -> ByteString -> Maybe (DecimalFraction a, ByteString)
forall a.
Int -> ByteString -> Maybe (DecimalFraction a, ByteString)
start
where
start :: Int -> ByteString -> Maybe (DecimalFraction a, ByteString)
start !Int
p !ByteString
xs =
case (Word8 -> Bool) -> ByteString -> (Int, ByteString)
lengthDropWhile Word8 -> Bool
isDecimalZero ByteString
xs of
(Int
0, ByteString
_) -> Int -> ByteString -> Maybe (DecimalFraction a, ByteString)
forall a.
Int -> ByteString -> Maybe (DecimalFraction a, ByteString)
readWholePart Int
p ByteString
xs
(Int
_, ByteString
ys) ->
case ByteString -> Maybe (Word8, ByteString)
BS.uncons ByteString
ys of
Maybe (Word8, ByteString)
Nothing -> DecimalFraction a
-> ByteString -> Maybe (DecimalFraction a, ByteString)
forall a b. a -> b -> Maybe (a, b)
justPair (Integer -> Int -> DecimalFraction a
forall a. Integer -> Int -> DecimalFraction a
DF Integer
0 Int
0) ByteString
BS.empty
Just (Word8
y0,ByteString
ys0)
| Word8 -> Bool
isDecimal Word8
y0 -> Int -> ByteString -> Maybe (DecimalFraction a, ByteString)
forall a.
Int -> ByteString -> Maybe (DecimalFraction a, ByteString)
readWholePart Int
p ByteString
ys
| Word8 -> Bool
isNotPeriod Word8
y0 -> DecimalFraction a
-> ByteString -> Maybe (DecimalFraction a, ByteString)
forall a b. a -> b -> Maybe (a, b)
justPair (Integer -> Int -> DecimalFraction a
forall a. Integer -> Int -> DecimalFraction a
DF Integer
0 Int
0) ByteString
ys
| Bool
otherwise ->
case (Word8 -> Bool) -> ByteString -> (Int, ByteString)
lengthDropWhile Word8 -> Bool
isDecimalZero ByteString
ys0 of
(Int
0, ByteString
_) -> Int
-> Integer -> ByteString -> Maybe (DecimalFraction a, ByteString)
forall a.
Int
-> Integer -> ByteString -> Maybe (DecimalFraction a, ByteString)
readFractionPart Int
p Integer
0 ByteString
ys
(Int
scale, ByteString
zs) -> Int -> Int -> ByteString -> Maybe (DecimalFraction a, ByteString)
forall a.
Int -> Int -> ByteString -> Maybe (DecimalFraction a, ByteString)
afterDroppingZeroes Int
p Int
scale ByteString
zs
afterDroppingZeroes :: Int -> Int -> ByteString -> Maybe (DecimalFraction a, ByteString)
afterDroppingZeroes !Int
p !Int
scale !ByteString
xs =
let ys :: ByteString
ys = Int -> ByteString -> ByteString
BS.take Int
p ByteString
xs in
case ByteString -> Maybe (Integer, ByteString)
forall a. Integral a => ByteString -> Maybe (a, ByteString)
I.readDecimal ByteString
ys of
Maybe (Integer, ByteString)
Nothing -> DecimalFraction a
-> ByteString -> Maybe (DecimalFraction a, ByteString)
forall a b. a -> b -> Maybe (a, b)
justPair (Integer -> Int -> DecimalFraction a
forall a. Integer -> Int -> DecimalFraction a
DF Integer
0 Int
0) ByteString
xs
Just (Integer
part, ByteString
ys') ->
let scale' :: Int
scale' = Int
scale Int -> Int -> Int
forall a. Num a => a -> a -> a
+ ByteString -> Int
BS.length ByteString
xs Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
BS.length ByteString
ys'
in DecimalFraction a
-> ByteString -> Maybe (DecimalFraction a, ByteString)
forall a b. a -> b -> Maybe (a, b)
justPair (Integer -> Int -> DecimalFraction a
forall a. Integer -> Int -> DecimalFraction a
DF Integer
part (Int -> Int
forall a. Num a => a -> a
negate Int
scale'))
((Word8 -> Bool) -> ByteString -> ByteString
BS.dropWhile Word8 -> Bool
isDecimal ByteString
ys')
readWholePart :: Int -> ByteString -> Maybe (DecimalFraction a, ByteString)
readWholePart !Int
p !ByteString
xs =
let ys :: ByteString
ys = Int -> ByteString -> ByteString
BS.take Int
p ByteString
xs in
case ByteString -> Maybe (Integer, ByteString)
forall a. Integral a => ByteString -> Maybe (a, ByteString)
I.readDecimal ByteString
ys of
Maybe (Integer, ByteString)
Nothing -> Maybe (DecimalFraction a, ByteString)
forall a. Maybe a
Nothing
Just (Integer
whole, ByteString
ys')
| ByteString -> Bool
BS.null ByteString
ys' ->
case (Word8 -> Bool) -> ByteString -> (Int, ByteString)
lengthDropWhile Word8 -> Bool
isDecimal (Int -> ByteString -> ByteString
BS.drop Int
p ByteString
xs) of
(Int
scale, ByteString
zs) ->
DecimalFraction a
-> ByteString -> Maybe (DecimalFraction a, ByteString)
forall a b. a -> b -> Maybe (a, b)
justPair (Integer -> Int -> DecimalFraction a
forall a. Integer -> Int -> DecimalFraction a
DF Integer
whole Int
scale) (ByteString -> ByteString
dropFractionPart ByteString
zs)
| Bool
otherwise ->
let len :: Int
len = ByteString -> Int
BS.length ByteString
ys Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
BS.length ByteString
ys'
xs' :: ByteString
xs' = Int -> ByteString -> ByteString
BS.drop Int
len ByteString
xs
in
if Word8 -> Bool
isNotPeriod (ByteString -> Word8
BSU.unsafeHead ByteString
xs')
then DecimalFraction a
-> ByteString -> Maybe (DecimalFraction a, ByteString)
forall a b. a -> b -> Maybe (a, b)
justPair (Integer -> Int -> DecimalFraction a
forall a. Integer -> Int -> DecimalFraction a
DF Integer
whole Int
0) ByteString
xs'
else Int
-> Integer -> ByteString -> Maybe (DecimalFraction a, ByteString)
forall a.
Int
-> Integer -> ByteString -> Maybe (DecimalFraction a, ByteString)
readFractionPart (Int
pInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
len) Integer
whole ByteString
xs'
dropFractionPart :: ByteString -> ByteString
dropFractionPart !ByteString
xs =
case ByteString -> Maybe (Word8, ByteString)
BS.uncons ByteString
xs of
Maybe (Word8, ByteString)
Nothing -> ByteString
BS.empty
Just (Word8
x0,ByteString
xs0)
| Word8 -> Bool
isNotPeriod Word8
x0 -> ByteString
xs
| Bool
otherwise ->
case ByteString -> Maybe (Word8, ByteString)
BS.uncons ByteString
xs0 of
Maybe (Word8, ByteString)
Nothing -> Word8 -> ByteString
BS.singleton Word8
0x2E
Just (Word8
x1,ByteString
xs1)
| Word8 -> Bool
isDecimal Word8
x1 -> (Word8 -> Bool) -> ByteString -> ByteString
BS.dropWhile Word8 -> Bool
isDecimal ByteString
xs1
| Bool
otherwise -> ByteString
xs
readFractionPart :: Int
-> Integer -> ByteString -> Maybe (DecimalFraction a, ByteString)
readFractionPart !Int
p !Integer
whole !ByteString
xs =
let ys :: ByteString
ys = Int -> ByteString -> ByteString
BS.take Int
p (ByteString -> ByteString
BSU.unsafeTail ByteString
xs) in
case ByteString -> Maybe (Integer, ByteString)
forall a. Integral a => ByteString -> Maybe (a, ByteString)
I.readDecimal ByteString
ys of
Maybe (Integer, ByteString)
Nothing -> DecimalFraction a
-> ByteString -> Maybe (DecimalFraction a, ByteString)
forall a b. a -> b -> Maybe (a, b)
justPair (Integer -> Int -> DecimalFraction a
forall a. Integer -> Int -> DecimalFraction a
DF Integer
whole Int
0) ByteString
xs
Just (Integer
part, ByteString
ys') ->
let scale :: Int
scale = ByteString -> Int
BS.length ByteString
ys Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
BS.length ByteString
ys'
in DecimalFraction a
-> ByteString -> Maybe (DecimalFraction a, ByteString)
forall a b. a -> b -> Maybe (a, b)
justPair (Integer -> Int -> Integer -> DecimalFraction a
forall a. Integer -> Int -> Integer -> DecimalFraction a
fractionDF Integer
whole Int
scale Integer
part)
((Word8 -> Bool) -> ByteString -> ByteString
BS.dropWhile Word8 -> Bool
isDecimal (Int -> ByteString -> ByteString
BS.drop (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
scale) ByteString
xs))
readExponentialLimited :: (Fractional a) => Int -> ByteString -> Maybe (a, ByteString)
{-# SPECIALIZE readExponentialLimited ::
Int -> ByteString -> Maybe (Float, ByteString),
Int -> ByteString -> Maybe (Double, ByteString),
Int -> ByteString -> Maybe (Rational, ByteString) #-}
readExponentialLimited :: Int -> ByteString -> Maybe (a, ByteString)
readExponentialLimited = Int -> ByteString -> Maybe (a, ByteString)
forall a.
Fractional a =>
Int -> ByteString -> Maybe (a, ByteString)
start
where
start :: Int -> ByteString -> Maybe (a, ByteString)
start !Int
p !ByteString
xs =
case Int -> ByteString -> Maybe (DecimalFraction a, ByteString)
forall a.
Fractional a =>
Int -> ByteString -> Maybe (DecimalFraction a, ByteString)
readDecimalLimited_ Int
p ByteString
xs of
Maybe (DecimalFraction a, ByteString)
Nothing -> Maybe (a, ByteString)
forall a. Maybe a
Nothing
Just (DecimalFraction a
df,ByteString
xs') -> (a, ByteString) -> Maybe (a, ByteString)
forall a. a -> Maybe a
Just ((a, ByteString) -> Maybe (a, ByteString))
-> (a, ByteString) -> Maybe (a, ByteString)
forall a b. (a -> b) -> a -> b
$! DecimalFraction a -> ByteString -> (a, ByteString)
forall a.
Fractional a =>
DecimalFraction a -> ByteString -> (a, ByteString)
readExponentPart DecimalFraction a
df ByteString
xs'
readExponentPart :: DecimalFraction a -> ByteString -> (a, ByteString)
readExponentPart !DecimalFraction a
df !ByteString
xs
| ByteString -> Bool
BS.null ByteString
xs = a -> ByteString -> (a, ByteString)
forall a b. a -> b -> (a, b)
pair (DecimalFraction a -> a
forall a. Fractional a => DecimalFraction a -> a
fromDF DecimalFraction a
df) ByteString
BS.empty
| Word8 -> Bool
isNotE (ByteString -> Word8
BSU.unsafeHead ByteString
xs) = a -> ByteString -> (a, ByteString)
forall a b. a -> b -> (a, b)
pair (DecimalFraction a -> a
forall a. Fractional a => DecimalFraction a -> a
fromDF DecimalFraction a
df) ByteString
xs
| Bool
otherwise =
case (ByteString -> Maybe (Int, ByteString))
-> ByteString -> Maybe (Int, ByteString)
forall a.
Num a =>
(ByteString -> Maybe (a, ByteString))
-> ByteString -> Maybe (a, ByteString)
readSigned ByteString -> Maybe (Int, ByteString)
forall a. Integral a => ByteString -> Maybe (a, ByteString)
I.readDecimal (ByteString -> ByteString
BSU.unsafeTail ByteString
xs) of
Maybe (Int, ByteString)
Nothing -> a -> ByteString -> (a, ByteString)
forall a b. a -> b -> (a, b)
pair (DecimalFraction a -> a
forall a. Fractional a => DecimalFraction a -> a
fromDF DecimalFraction a
df) ByteString
xs
Just (Int
scale, ByteString
xs') -> a -> ByteString -> (a, ByteString)
forall a b. a -> b -> (a, b)
pair (DecimalFraction a -> a
forall a. Fractional a => DecimalFraction a -> a
fromDF (DecimalFraction a -> a) -> DecimalFraction a -> a
forall a b. (a -> b) -> a -> b
$ DecimalFraction a -> Int -> DecimalFraction a
forall a. DecimalFraction a -> Int -> DecimalFraction a
scaleDF DecimalFraction a
df Int
scale) ByteString
xs'