Make ‘float’ consume only floating point literals

Now it no longer accepts plain integers, which should be a better behavior.
This commit is contained in:
mrkkrp 2017-09-21 21:37:22 +07:00
parent 10c3d7b6cf
commit 07160049a8
5 changed files with 104 additions and 62 deletions

View File

@ -1,3 +1,9 @@
## Megaparsec 6.2.0
* `float` in `Text.Megaparsec.Char.Lexer` and `Text.Megaparsec.Byte.Lexer`
now does not accept plain integers. This is the behavior we had in version
5 of the library.
## Megaparsec 6.1.1
* Fixed the bug when `tokens` used `cok` continuation even when matching an

View File

@ -179,38 +179,52 @@ scientific
:: forall e s m. (MonadParsec e s m, Token s ~ Word8)
=> m Scientific
scientific = do
let pxy = Proxy :: Proxy s
c' <- decimal_
SP c e' <- option (SP c' 0) $ do
SP c e' <- option (SP c' 0) (dotDecimal_ (Proxy :: Proxy s) c')
e <- option e' (exponent_ e')
return (Sci.scientific c e)
{-# INLINEABLE scientific #-}
data SP = SP !Integer {-# UNPACK #-} !Int
-- | Parse a floating point number according to the syntax for floating
-- point literals described in the Haskell report.
--
-- This function does not parse sign, if you need to parse signed numbers,
-- see 'signed'.
--
-- __Note__: in versions 6.0.06.1.1 this function accepted plain integers.
float :: (MonadParsec e s m, Token s ~ Word8, RealFloat a) => m a
float = do
c' <- decimal_
Sci.toRealFloat <$>
((do SP c e' <- dotDecimal_ (Proxy :: Proxy s) c'
e <- option e' (exponent_ e')
return (Sci.scientific c e))
<|> (Sci.scientific c' <$> exponent_ 0))
{-# INLINEABLE float #-}
dotDecimal_ :: (MonadParsec e s m, Token s ~ Word8)
=> Proxy s
-> Integer
-> m SP
dotDecimal_ pxy c' = do
void (char 46)
let mkNum = foldl' step (SP c' 0) . chunkToTokens pxy
step (SP a e') w = SP
(a * 10 + fromIntegral (w - 48))
(e' - 1)
mkNum <$> takeWhile1P (Just "digit") isDigit
e <- option e' $ do
{-# INLINE dotDecimal_ #-}
exponent_ :: (MonadParsec e s m, Token s ~ Word8)
=> Int
-> m Int
exponent_ e' = do
void (char' 101)
(+ e') <$> signed (return ()) decimal_
return (Sci.scientific c e)
{-# INLINEABLE scientific #-}
data SP = SP !Integer {-# UNPACK #-} !Int
-- | Parse a floating point number without sign. There are differences
-- between the syntax for floating point literals described in the Haskell
-- report and what this function accepts. In particular, it does not require
-- fractional part and accepts inputs like @\"3\"@ returning @3.0@.
--
-- This is a simple short-cut defined as:
--
-- > float = Sci.toRealFloat <$> scientific <?> "floating point number"
--
-- This function does not parse sign, if you need to parse signed numbers,
-- see 'signed'.
float :: (MonadParsec e s m, Token s ~ Word8, RealFloat a) => m a
float = Sci.toRealFloat <$> scientific <?> "floating point number"
{-# INLINEABLE float #-}
{-# INLINE exponent_ #-}
-- | @'signed' space p@ parser parses an optional sign character (“+” or
-- “-”), then if there is a sign it consumes optional white space (using

View File

@ -495,42 +495,56 @@ scientific
:: forall e s m. (MonadParsec e s m, Token s ~ Char)
=> m Scientific
scientific = do
let pxy = Proxy :: Proxy s
c' <- decimal_
SP c e' <- option (SP c' 0) $ do
void (C.char '.')
let mkNum = foldl' step (SP c' 0) . chunkToTokens pxy
step (SP a e') c = SP
(a * 10 + fromIntegral (Char.digitToInt c))
(e' - 1)
mkNum <$> takeWhile1P (Just "digit") Char.isDigit
e <- option e' $ do
void (C.char' 'e')
(+ e') <$> signed (return ()) decimal_
SP c e' <- option (SP c' 0) (dotDecimal_ (Proxy :: Proxy s) c')
e <- option e' (exponent_ e')
return (Sci.scientific c e)
{-# INLINEABLE scientific #-}
data SP = SP !Integer {-# UNPACK #-} !Int
-- | Parse a floating point number without sign. There are differences
-- between the syntax for floating point literals described in the Haskell
-- report and what this function accepts. In particular, it does not require
-- fractional part and accepts inputs like @\"3\"@ returning @3.0@.
--
-- This is a simple short-cut defined as:
--
-- > float = Sci.toRealFloat <$> scientific <?> "floating point number"
-- | Parse a floating point number according to the syntax for floating
-- point literals described in the Haskell report.
--
-- This function does not parse sign, if you need to parse signed numbers,
-- see 'signed'.
--
-- __Note__: before version 6.0.0 the function returned 'Double', i.e. it
-- wasn't polymorphic in its return type.
--
-- __Note__: in versions 6.0.06.1.1 this function accepted plain integers.
float :: (MonadParsec e s m, Token s ~ Char, RealFloat a) => m a
float = Sci.toRealFloat <$> scientific <?> "floating point number"
float = do
c' <- decimal_
Sci.toRealFloat <$>
((do SP c e' <- dotDecimal_ (Proxy :: Proxy s) c'
e <- option e' (exponent_ e')
return (Sci.scientific c e))
<|> (Sci.scientific c' <$> exponent_ 0))
{-# INLINEABLE float #-}
dotDecimal_ :: (MonadParsec e s m, Token s ~ Char)
=> Proxy s
-> Integer
-> m SP
dotDecimal_ pxy c' = do
void (C.char '.')
let mkNum = foldl' step (SP c' 0) . chunkToTokens pxy
step (SP a e') c = SP
(a * 10 + fromIntegral (Char.digitToInt c))
(e' - 1)
mkNum <$> takeWhile1P (Just "digit") Char.isDigit
{-# INLINE dotDecimal_ #-}
exponent_ :: (MonadParsec e s m, Token s ~ Char)
=> Int
-> m Int
exponent_ e' = do
void (C.char' 'e')
(+ e') <$> signed (return ()) decimal_
{-# INLINE exponent_ #-}
-- | @'signed' space p@ parser parses an optional sign character (“+” or
-- “-”), then if there is a sign it consumes optional white space (using
-- @space@ parser), then it runs parser @p@ which should return a number.

View File

@ -138,26 +138,30 @@ spec = do
let p = float :: Parser Double
s = B.pack (a : as)
prs p s `shouldFailWith`
err posI (utok a <> elabel "floating point number")
err posI (utok a <> elabel "digit")
prs' p s `failsLeaving` s
context "when stream begins with a decimal number" $
it "parses it" $
context "when stream begins with an integer (decimal)" $
it "signals correct parse error" $
property $ \n' -> do
let p = float :: Parser Double
n = getNonNegative n'
s = B8.pack $ show (n :: Integer)
prs p s `shouldParse` fromIntegral n
prs' p s `succeedsLeaving` ""
prs p s `shouldFailWith` err (posN (B.length s) s)
(ueof <> etok 46 <> etok 69 <> etok 101 <> elabel "digit")
prs' p s `failsLeaving` ""
context "when stream is empty" $
it "signals correct parse error" $
prs (float :: Parser Double) "" `shouldFailWith`
err posI (ueof <> elabel "floating point number")
context "when there is float with exponent without explicit sign" $
err posI (ueof <> elabel "digit")
context "when there is float with just exponent" $
it "parses it all right" $ do
let p = float :: Parser Double
s = "123e3"
prs p s `shouldParse` 123e3
prs' p s `succeedsLeaving` ""
prs p "123e3" `shouldParse` 123e3
prs' p "123e3" `succeedsLeaving` ""
prs p "123e+3" `shouldParse` 123e+3
prs' p "123e+3" `succeedsLeaving` ""
prs p "123e-3" `shouldParse` 123e-3
prs' p "123e-3" `succeedsLeaving` ""
describe "scientific" $ do
context "when stream begins with a number" $

View File

@ -336,26 +336,30 @@ spec = do
let p = float :: Parser Double
s = a : as
prs p s `shouldFailWith`
err posI (utok a <> elabel "floating point number")
err posI (utok a <> elabel "digit")
prs' p s `failsLeaving` s
context "when stream begins with a decimal number" $
it "parses it" $
context "when stream begins with an integer (decimal)" $
it "signals correct parse error" $
property $ \n' -> do
let p = float :: Parser Double
n = getNonNegative n'
s = show (n :: Integer)
prs p s `shouldParse` fromIntegral n
prs' p s `succeedsLeaving` ""
prs p s `shouldFailWith` err (posN (length s) s)
(ueof <> etok '.' <> etok 'E' <> etok 'e' <> elabel "digit")
prs' p s `failsLeaving` ""
context "when stream is empty" $
it "signals correct parse error" $
prs (float :: Parser Double) "" `shouldFailWith`
err posI (ueof <> elabel "floating point number")
context "when there is float with exponent without explicit sign" $
err posI (ueof <> elabel "digit")
context "when there is float with just exponent" $
it "parses it all right" $ do
let p = float :: Parser Double
s = "123e3"
prs p s `shouldParse` 123e3
prs' p s `succeedsLeaving` ""
prs p "123e3" `shouldParse` 123e3
prs' p "123e3" `succeedsLeaving` ""
prs p "123e+3" `shouldParse` 123e+3
prs' p "123e+3" `succeedsLeaving` ""
prs p "123e-3" `shouldParse` 123e-3
prs' p "123e-3" `succeedsLeaving` ""
describe "scientific" $ do
context "when stream begins with a number" $