Skip to content

Commit 42de75f

Browse files
committed
feat: add parser for decimal numbers
1 parent ee13357 commit 42de75f

File tree

2 files changed

+29
-5
lines changed

2 files changed

+29
-5
lines changed

src/Text/Megaparsec/Utils.hs

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -8,13 +8,15 @@ module Text.Megaparsec.Utils
88
, occurrence
99
, occurrences
1010
, parsecToReadsPrec
11+
, posDecNumParser
1112
, posNumParser
1213
, uuidParser
1314
) where
1415

1516
import Control.Applicative (many, some, (<|>))
1617
import Control.Applicative.Combinators (choice)
1718
import Control.Monad (replicateM, void)
19+
import Control.Monad.Combinators (optional)
1820
import Data.Functor (($>))
1921
import Data.List (intercalate, sortOn)
2022
import Data.List.NonEmpty (NonEmpty ((:|)))
@@ -58,6 +60,14 @@ occurrence p = go
5860
occurrences :: Parsec Void String a -> Parsec Void String [a]
5961
occurrences = some . try . occurrence
6062

63+
-- | Parse a positive number with decimals.
64+
posDecNumParser :: Parsec Void String Double
65+
posDecNumParser = do
66+
num <- some digitChar
67+
den <- maybe "" ("." <>) <$> optional (char '.' >> some digitChar)
68+
69+
return . read $ num <> den
70+
6171
-- | Parse a positive integer.
6272
posNumParser :: Read a => Parsec Void String a
6373
posNumParser = read <$> some digitChar

test/Text/Megaparsec/UtilsSpec.hs

Lines changed: 19 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,3 @@
1-
{-# LANGUAGE TypeApplications #-}
21
{-# OPTIONS_GHC -Wno-orphans #-}
32

43
module Text.Megaparsec.UtilsSpec
@@ -25,8 +24,10 @@ import Text.Megaparsec (Parsec, eof, parseMaybe,
2524
import Text.Megaparsec.Char (alphaNumChar, char, digitChar,
2625
string)
2726
import Text.Megaparsec.Utils (boundedEnumShowParser,
28-
commaSeparated, occurrence,
29-
occurrences)
27+
commaSeparated, numParser,
28+
occurrence, occurrences,
29+
posDecNumParser, posNumParser)
30+
import Text.Printf (printf)
3031

3132
newtype SomeData = SomeData Int
3233
deriving Eq
@@ -112,6 +113,21 @@ spec = do
112113
it "SomeADT" . property $ \v ->
113114
parseMaybe someADTParser (show (v :: SomeADT)) `shouldBe` Just v
114115

116+
context "posDecNumParser" $ do
117+
it "no decimals" . property $ \v ->
118+
parseMaybe posDecNumParser (show (abs (v :: Int))) `shouldBe`
119+
Just (fromIntegral (abs v))
120+
121+
it "decimals" . property $ \v ->
122+
parseMaybe posDecNumParser (printf "%f" (abs (v :: Double))) `shouldBe`
123+
Just (abs v)
124+
125+
it "posNumParser" . property $ \v ->
126+
parseMaybe posNumParser (show (abs (v :: Int))) `shouldBe` Just (abs v)
127+
128+
it "numParser" . property $ \v ->
129+
parseMaybe numParser (show (v :: Int)) `shouldBe` Just v
130+
115131
describe "boundedEnumShowParser" $ do
116132
context "lowercase" . exhaustive $ \v ->
117133
parseMaybe (boundedEnumShowParser <* eof) (show v) `shouldBe` Just (v :: SomeEnum)
@@ -154,8 +170,6 @@ spec = do
154170
runParser (occurrences someADTParser) "test" s `shouldBe` Right [v]
155171

156172
describe "comma-separated" $ do
157-
let numParser = read @Int <$> some digitChar
158-
159173
context "valid" $ do
160174
it "single" . property $ \x -> do
161175
let y = abs x

0 commit comments

Comments
 (0)