mirror of
https://github.com/mrkkrp/megaparsec.git
synced 2024-11-27 07:31:24 +03:00
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:
parent
10c3d7b6cf
commit
07160049a8
@ -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
|
## Megaparsec 6.1.1
|
||||||
|
|
||||||
* Fixed the bug when `tokens` used `cok` continuation even when matching an
|
* Fixed the bug when `tokens` used `cok` continuation even when matching an
|
||||||
|
@ -179,39 +179,53 @@ scientific
|
|||||||
:: forall e s m. (MonadParsec e s m, Token s ~ Word8)
|
:: forall e s m. (MonadParsec e s m, Token s ~ Word8)
|
||||||
=> m Scientific
|
=> m Scientific
|
||||||
scientific = do
|
scientific = do
|
||||||
let pxy = Proxy :: Proxy s
|
c' <- decimal_
|
||||||
c' <- decimal_
|
SP c e' <- option (SP c' 0) (dotDecimal_ (Proxy :: Proxy s) c')
|
||||||
SP c e' <- option (SP c' 0) $ do
|
e <- option e' (exponent_ e')
|
||||||
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
|
|
||||||
void (char' 101)
|
|
||||||
(+ e') <$> signed (return ()) decimal_
|
|
||||||
return (Sci.scientific c e)
|
return (Sci.scientific c e)
|
||||||
{-# INLINEABLE scientific #-}
|
{-# INLINEABLE scientific #-}
|
||||||
|
|
||||||
data SP = SP !Integer {-# UNPACK #-} !Int
|
data SP = SP !Integer {-# UNPACK #-} !Int
|
||||||
|
|
||||||
-- | Parse a floating point number without sign. There are differences
|
-- | Parse a floating point number according to the syntax for floating
|
||||||
-- between the syntax for floating point literals described in the Haskell
|
-- point literals described in the Haskell report.
|
||||||
-- 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,
|
-- This function does not parse sign, if you need to parse signed numbers,
|
||||||
-- see 'signed'.
|
-- see 'signed'.
|
||||||
|
--
|
||||||
|
-- __Note__: in versions 6.0.0–6.1.1 this function accepted plain integers.
|
||||||
|
|
||||||
float :: (MonadParsec e s m, Token s ~ Word8, RealFloat a) => m a
|
float :: (MonadParsec e s m, Token s ~ Word8, 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 #-}
|
{-# 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
|
||||||
|
{-# INLINE dotDecimal_ #-}
|
||||||
|
|
||||||
|
exponent_ :: (MonadParsec e s m, Token s ~ Word8)
|
||||||
|
=> Int
|
||||||
|
-> m Int
|
||||||
|
exponent_ e' = do
|
||||||
|
void (char' 101)
|
||||||
|
(+ e') <$> signed (return ()) decimal_
|
||||||
|
{-# INLINE exponent_ #-}
|
||||||
|
|
||||||
-- | @'signed' space p@ parser parses an optional sign character (“+” or
|
-- | @'signed' space p@ parser parses an optional sign character (“+” or
|
||||||
-- “-”), then if there is a sign it consumes optional white space (using
|
-- “-”), then if there is a sign it consumes optional white space (using
|
||||||
-- @space@ parser), then it runs parser @p@ which should return a number.
|
-- @space@ parser), then it runs parser @p@ which should return a number.
|
||||||
|
@ -495,42 +495,56 @@ scientific
|
|||||||
:: forall e s m. (MonadParsec e s m, Token s ~ Char)
|
:: forall e s m. (MonadParsec e s m, Token s ~ Char)
|
||||||
=> m Scientific
|
=> m Scientific
|
||||||
scientific = do
|
scientific = do
|
||||||
let pxy = Proxy :: Proxy s
|
c' <- decimal_
|
||||||
c' <- decimal_
|
SP c e' <- option (SP c' 0) (dotDecimal_ (Proxy :: Proxy s) c')
|
||||||
SP c e' <- option (SP c' 0) $ do
|
e <- option e' (exponent_ e')
|
||||||
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_
|
|
||||||
return (Sci.scientific c e)
|
return (Sci.scientific c e)
|
||||||
{-# INLINEABLE scientific #-}
|
{-# INLINEABLE scientific #-}
|
||||||
|
|
||||||
data SP = SP !Integer {-# UNPACK #-} !Int
|
data SP = SP !Integer {-# UNPACK #-} !Int
|
||||||
|
|
||||||
-- | Parse a floating point number without sign. There are differences
|
-- | Parse a floating point number according to the syntax for floating
|
||||||
-- between the syntax for floating point literals described in the Haskell
|
-- point literals described in the Haskell report.
|
||||||
-- 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,
|
-- This function does not parse sign, if you need to parse signed numbers,
|
||||||
-- see 'signed'.
|
-- see 'signed'.
|
||||||
--
|
--
|
||||||
-- __Note__: before version 6.0.0 the function returned 'Double', i.e. it
|
-- __Note__: before version 6.0.0 the function returned 'Double', i.e. it
|
||||||
-- wasn't polymorphic in its return type.
|
-- wasn't polymorphic in its return type.
|
||||||
|
--
|
||||||
|
-- __Note__: in versions 6.0.0–6.1.1 this function accepted plain integers.
|
||||||
|
|
||||||
float :: (MonadParsec e s m, Token s ~ Char, RealFloat a) => m a
|
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 #-}
|
{-# 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
|
-- | @'signed' space p@ parser parses an optional sign character (“+” or
|
||||||
-- “-”), then if there is a sign it consumes optional white space (using
|
-- “-”), then if there is a sign it consumes optional white space (using
|
||||||
-- @space@ parser), then it runs parser @p@ which should return a number.
|
-- @space@ parser), then it runs parser @p@ which should return a number.
|
||||||
|
@ -138,26 +138,30 @@ spec = do
|
|||||||
let p = float :: Parser Double
|
let p = float :: Parser Double
|
||||||
s = B.pack (a : as)
|
s = B.pack (a : as)
|
||||||
prs p s `shouldFailWith`
|
prs p s `shouldFailWith`
|
||||||
err posI (utok a <> elabel "floating point number")
|
err posI (utok a <> elabel "digit")
|
||||||
prs' p s `failsLeaving` s
|
prs' p s `failsLeaving` s
|
||||||
context "when stream begins with a decimal number" $
|
context "when stream begins with an integer (decimal)" $
|
||||||
it "parses it" $
|
it "signals correct parse error" $
|
||||||
property $ \n' -> do
|
property $ \n' -> do
|
||||||
let p = float :: Parser Double
|
let p = float :: Parser Double
|
||||||
n = getNonNegative n'
|
n = getNonNegative n'
|
||||||
s = B8.pack $ show (n :: Integer)
|
s = B8.pack $ show (n :: Integer)
|
||||||
prs p s `shouldParse` fromIntegral n
|
prs p s `shouldFailWith` err (posN (B.length s) s)
|
||||||
prs' p s `succeedsLeaving` ""
|
(ueof <> etok 46 <> etok 69 <> etok 101 <> elabel "digit")
|
||||||
|
prs' p s `failsLeaving` ""
|
||||||
context "when stream is empty" $
|
context "when stream is empty" $
|
||||||
it "signals correct parse error" $
|
it "signals correct parse error" $
|
||||||
prs (float :: Parser Double) "" `shouldFailWith`
|
prs (float :: Parser Double) "" `shouldFailWith`
|
||||||
err posI (ueof <> elabel "floating point number")
|
err posI (ueof <> elabel "digit")
|
||||||
context "when there is float with exponent without explicit sign" $
|
context "when there is float with just exponent" $
|
||||||
it "parses it all right" $ do
|
it "parses it all right" $ do
|
||||||
let p = float :: Parser Double
|
let p = float :: Parser Double
|
||||||
s = "123e3"
|
prs p "123e3" `shouldParse` 123e3
|
||||||
prs p s `shouldParse` 123e3
|
prs' p "123e3" `succeedsLeaving` ""
|
||||||
prs' p s `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
|
describe "scientific" $ do
|
||||||
context "when stream begins with a number" $
|
context "when stream begins with a number" $
|
||||||
|
@ -336,26 +336,30 @@ spec = do
|
|||||||
let p = float :: Parser Double
|
let p = float :: Parser Double
|
||||||
s = a : as
|
s = a : as
|
||||||
prs p s `shouldFailWith`
|
prs p s `shouldFailWith`
|
||||||
err posI (utok a <> elabel "floating point number")
|
err posI (utok a <> elabel "digit")
|
||||||
prs' p s `failsLeaving` s
|
prs' p s `failsLeaving` s
|
||||||
context "when stream begins with a decimal number" $
|
context "when stream begins with an integer (decimal)" $
|
||||||
it "parses it" $
|
it "signals correct parse error" $
|
||||||
property $ \n' -> do
|
property $ \n' -> do
|
||||||
let p = float :: Parser Double
|
let p = float :: Parser Double
|
||||||
n = getNonNegative n'
|
n = getNonNegative n'
|
||||||
s = show (n :: Integer)
|
s = show (n :: Integer)
|
||||||
prs p s `shouldParse` fromIntegral n
|
prs p s `shouldFailWith` err (posN (length s) s)
|
||||||
prs' p s `succeedsLeaving` ""
|
(ueof <> etok '.' <> etok 'E' <> etok 'e' <> elabel "digit")
|
||||||
|
prs' p s `failsLeaving` ""
|
||||||
context "when stream is empty" $
|
context "when stream is empty" $
|
||||||
it "signals correct parse error" $
|
it "signals correct parse error" $
|
||||||
prs (float :: Parser Double) "" `shouldFailWith`
|
prs (float :: Parser Double) "" `shouldFailWith`
|
||||||
err posI (ueof <> elabel "floating point number")
|
err posI (ueof <> elabel "digit")
|
||||||
context "when there is float with exponent without explicit sign" $
|
context "when there is float with just exponent" $
|
||||||
it "parses it all right" $ do
|
it "parses it all right" $ do
|
||||||
let p = float :: Parser Double
|
let p = float :: Parser Double
|
||||||
s = "123e3"
|
prs p "123e3" `shouldParse` 123e3
|
||||||
prs p s `shouldParse` 123e3
|
prs' p "123e3" `succeedsLeaving` ""
|
||||||
prs' p s `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
|
describe "scientific" $ do
|
||||||
context "when stream begins with a number" $
|
context "when stream begins with a number" $
|
||||||
|
Loading…
Reference in New Issue
Block a user