1
1
mirror of https://github.com/github/semantic.git synced 2024-12-02 11:23:05 +03:00

Merge remote-tracking branch 'origin/master' into move-semantic-lib

This commit is contained in:
Patrick Thomson 2020-06-29 14:48:49 -04:00
commit 29d3d09ee0
4 changed files with 1 additions and 42 deletions

View File

@ -103,8 +103,6 @@ library
, Data.Map.Monoidal
, Data.Maybe.Exts
, Data.Semigroup.App
, Data.Scientific.Exts
, Numeric.Exts
-- Parser glue
, Parsing.Parser
, Parsing.TreeSitter
@ -149,16 +147,13 @@ library
, haskeline ^>= 0.7.5.0
, hostname ^>= 1.0
, hscolour ^>= 1.24.4
, kdt ^>= 0.2.4
, lens >= 4.17 && < 4.19
, mersenne-random-pure64 ^>= 0.2.2.0
, network-uri ^>= 2.6.1.0
, optparse-applicative >= 0.14.3 && < 0.16
, parallel ^>= 3.2.2.0
, parsers ^>= 0.12.9
, prettyprinter >= 1.2 && < 2
, pretty-show ^>= 1.9.5
, profunctors ^>= 5.3
, proto-lens >= 0.5 && < 0.7
, reducers ^>= 3.12.3
, semantic-go ^>= 0
@ -209,10 +204,8 @@ test-suite test
, Data.Functor.Listable
, Data.Graph.Spec
, Data.Language.Spec
, Data.Scientific.Spec
, Data.Semigroup.App.Spec
, Integration.Spec
, Numeric.Spec
, Semantic.Spec
, Semantic.CLI.Spec
, Semantic.IO.Spec

View File

@ -124,6 +124,7 @@ tsxSkips = Path.relFile <$>
typescriptSkips :: [Path.RelFile]
typescriptSkips = Path.relFile <$>
[ "npm/node_modules/slide/lib/async-map-ordered.js"
, "npm/node_modules/request/node_modules/har-validator/node_modules/ajv/dist/regenerator.min.js"
]
buildExamples :: TaskSession -> LanguageExample -> Path.RelDir -> IO Tasty.TestTree

View File

@ -1,44 +1,13 @@
{-# LANGUAGE OverloadedStrings #-}
module Generators
( source
, integerScientific
, rationalScientific
, floatingScientific
, classifyScientific
) where
import Data.Ratio ((%))
import Data.Scientific (Scientific)
import qualified Data.Scientific as Scientific
import Hedgehog
import qualified Hedgehog.Gen as Gen
import qualified Source.Source
source :: MonadGen m => Hedgehog.Range Int -> m Source.Source.Source
source r = Gen.frequency [ (1, empty), (20, nonEmpty) ]
where empty = pure mempty
nonEmpty = Source.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

@ -5,10 +5,8 @@ module Main (allTests, legacySpecs, main, tests) where
import qualified Data.Functor.Classes.Generic.Spec
import qualified Data.Graph.Spec
import qualified Data.Language.Spec
import qualified Data.Scientific.Spec
import qualified Data.Semigroup.App.Spec
import qualified Integration.Spec
import qualified Numeric.Spec
import qualified Tags.Spec
import qualified Semantic.Spec
import qualified Semantic.CLI.Spec
@ -23,10 +21,8 @@ import Test.Tasty.Hspec as Tasty
tests :: (?session :: TaskSession) => [TestTree]
tests =
[ Data.Language.Spec.testTree
, Data.Scientific.Spec.testTree
, Data.Semigroup.App.Spec.testTree
, Integration.Spec.testTree
, Numeric.Spec.testTree
, Semantic.CLI.Spec.testTree
, Semantic.Stat.Spec.testTree
]