1
1
mirror of https://github.com/github/semantic.git synced 2025-01-05 14:11:33 +03:00

Merge pull request #223 from github/property-test-scientific-parser

Property test scientific parser
This commit is contained in:
Rob Rix 2019-09-03 19:39:16 -04:00 committed by GitHub
commit 6507e6f147
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
3 changed files with 95 additions and 44 deletions

View File

@ -1,50 +1,70 @@
module Data.Scientific.Spec (spec) where
module Data.Scientific.Spec (testTree) where
import Data.Scientific.Exts
import Data.Either
import Data.Foldable (for_)
import SpecHelpers
import Data.Either
import Data.Foldable (for_)
import Data.Scientific.Exts
import Data.Text as Text
import qualified Generators as Gen
import Hedgehog
import qualified Hedgehog.Range as Range
import Test.Tasty as Tasty
import Test.Tasty.Hedgehog
import Test.Tasty.HUnit as HUnit
spec :: Spec
spec = describe "Scientific parsing" $ do
type Fixture = [(Text, Scientific)]
let go cases = for_ cases $ \(s, v) -> parseScientific s `shouldBe` Right v
testFixture :: [(Text, Scientific)] -> HUnit.Assertion
testFixture vals = for_ vals $ \(input, expected) -> assertEqual (Text.unpack input) (parseScientific input) (Right expected)
-- TODO: hexadecimal floats, someday (0x1.999999999999ap-4)
pythonSyntax :: Fixture
pythonSyntax = [ ("-.6_6", -0.66)
, ("+.1_1", 0.11)
, ("123.4123", 123.4123)
, ("123.123J", 123.123) -- TODO: handle complex values separately in the parser
, ("1_1.3_1", 11.31)
, ("1_1.", 11.0)
, ("99E+01", 99e1)
, ("1e+3_4j", 1e34)
, ("3.e14", 3e14)
, (".3e1_4", 0.3e14)
, ("1_0.l", 10) -- this and the subsequent ones don't actually seem to be valid syntax, we should fix this in tree-sitter
, (".3", 0.3)
, (".1l", 0.1) -- omitting a leading 0 is deprecated in python 3, also note that the -l suffix is not valid in Python 3
]
it "should handle Python floats" $
go [ ("-.6_6", -0.66)
, ("+.1_1", 0.11)
, ("123.4123", 123.4123)
, ("123.123J", 123.123) -- TODO: handle complex values separately in the parser
, ("1_1.3_1", 11.31)
, ("1_1.", 11.0)
, ("99E+01", 99e1)
, ("1e+3_4j", 1e34)
, ("3.e14", 3e14)
, (".3e1_4", 0.3e14)
, ("1_0.l", 10) -- this and the subsequent ones don't actually seem to be valid syntax, we should fix this in tree-sitter
, (".3", 0.3)
, (".1l", 0.1) -- omitting a leading 0 is deprecated in python 3, also note that the -l suffix is not valid in Python 3
]
rubySyntax :: Fixture
rubySyntax = [ ("1.234_5e1_0", 1.2345e10)
, ("1E30", 1e30)
, ("1.2i", 1.2)
, ("1.0e+6", 1.0e6)
, ("1.0e-6", 1.0e-6)
]
it "should handle Ruby floats" $
go [ ("1.234_5e1_0", 1.2345e10)
, ("1E30", 1e30)
, ("1.2i", 1.2)
, ("1.0e+6", 1.0e6)
, ("1.0e-6", 1.0e-6)
]
jsSyntax :: Fixture
jsSyntax = [ ("101", 101)
, ("3.14", 3.14)
, ("3.14e+1", 3.14e1)
, ("0x1ABCDEFabcdef", 470375954370031)
, ("0o7632157312", 1047060170)
, ("0b1010101001", 681)
]
it "should handle JS numbers, including multiple bases" $
go [ ("101", 101)
, ("3.14", 3.14)
, ("3.14e+1", 3.14e1)
, ("0x1ABCDEFabcdef", 470375954370031)
, ("0o7632157312", 1047060170)
, ("0b1010101001", 681)
]
it "should not accept truly bad input" $ do
parseScientific "." `shouldSatisfy` isLeft
parseScientific "" `shouldSatisfy` isLeft
testTree :: Tasty.TestTree
testTree = testGroup "Data.Scientific.Exts"
[ testCase "Python float syntax" $ testFixture pythonSyntax
, testCase "Ruby float syntax" $ testFixture rubySyntax
, testCase "JavaScript float syntax" $ testFixture jsSyntax
, testCase "Pathological input" $ do
isLeft (parseScientific ".") @? "Accepted period"
isLeft (parseScientific "") @? "Accepted empty string"
, testProperty "Scientific roundtripping" . property $ do
let nrange = Range.linear (negate 500000) 20000000
drange = Range.exponential 1 100000000
fromRat <- forAll (Gen.rationalScientific nrange drange)
Gen.classifyScientific fromRat
tripping fromRat (pack . show) parseScientific
, testProperty "Double-based Scientific roundtripping" . property $ do
fromDbl <- forAll (Gen.floatingScientific (Range.linearFrac (negate 1) 3))
Gen.classifyScientific fromDbl
tripping fromDbl (pack . show) parseScientific
]

View File

@ -1,14 +1,45 @@
{-# LANGUAGE TypeFamilies #-}
module Generators
( source
, integerScientific
, rationalScientific
, floatingScientific
, classifyScientific
) where
import Hedgehog
import qualified Hedgehog.Gen as Gen
import qualified Data.Source
import Data.Functor.Identity
import Data.Scientific (Scientific)
import Data.Ratio ((%))
import qualified Data.Scientific as Scientific
source :: (GenBase m ~ Identity, MonadGen m) => Hedgehog.Range Int -> m Data.Source.Source
source r = Gen.frequency [ (1, empty), (20, nonEmpty) ]
where empty = pure mempty
nonEmpty = Data.Source.fromUTF8 <$> Gen.utf8 r (Gen.frequency [ (1, pure '\r'), (1, pure '\n'), (20, Gen.unicode) ])
integerScientific :: MonadGen m => Hedgehog.Range Integer -> m Scientific
integerScientific = fmap fromIntegral . Gen.integral
rationalScientific :: MonadGen m => Hedgehog.Range Integer -> Hedgehog.Range Integer -> m Scientific
rationalScientific nrange drange = do
num <- Gen.integral nrange
den <- Gen.integral drange
let goodDen = if den == 0 then 1 else den
let digitLimit = Just 25
case Scientific.fromRationalRepetend digitLimit (num % goodDen) of
Left (sci, _) -> pure sci
Right (sci, _) -> pure sci
floatingScientific :: MonadGen m => Hedgehog.Range Double -> m Scientific
floatingScientific = fmap Scientific.fromFloatDigits . Gen.double
classifyScientific :: MonadTest m => Scientific -> m ()
classifyScientific sci = do
classify "negative" $ sci < 0
classify "small" $ (sci > 0 && sci <= 1)
classify "medium" $ (sci > 1 && sci <= 10000)
classify "large" $ sci > 10000

View File

@ -50,6 +50,7 @@ tests =
, Data.Language.Spec.testTree
, Data.Source.Spec.testTree
, Semantic.Stat.Spec.testTree
, Data.Scientific.Spec.testTree
]
-- We can't bring this out of the IO monad until we divest
@ -81,7 +82,6 @@ legacySpecs = parallel $ do
describe "Data.Abstract.Name" Data.Abstract.Name.Spec.spec
describe "Data.Functor.Classes.Generic" Data.Functor.Classes.Generic.Spec.spec
describe "Data.Range" Data.Range.Spec.spec
describe "Data.Scientific" Data.Scientific.Spec.spec
describe "Data.Semigroup.App" Data.Semigroup.App.Spec.spec
describe "Data.Source" Data.Source.Spec.spec
describe "Data.Term" Data.Term.Spec.spec