1
1
mirror of https://github.com/github/semantic.git synced 2024-12-26 00:12:29 +03:00

Merge branch 'master' into ruby-match-syntax

This commit is contained in:
Patrick Thomson 2018-03-19 15:35:38 -04:00 committed by GitHub
commit d053da814b
9 changed files with 53 additions and 16 deletions

View File

@ -38,8 +38,8 @@ library
-- Control flow -- Control flow
, Control.Effect , Control.Effect
-- Effects used for program analysis -- Effects used for program analysis
, Control.Monad.Effect.Fresh , Control.Effect.Fresh
, Control.Monad.Effect.NonDet , Control.Effect.NonDet
-- Datatypes for abstract interpretation -- Datatypes for abstract interpretation
, Data.Abstract.Address , Data.Abstract.Address
, Data.Abstract.Cache , Data.Abstract.Cache
@ -257,6 +257,16 @@ test-suite test
default-language: Haskell2010 default-language: Haskell2010
default-extensions: DeriveFunctor, DeriveGeneric, FlexibleContexts, FlexibleInstances, OverloadedStrings, RecordWildCards default-extensions: DeriveFunctor, DeriveGeneric, FlexibleContexts, FlexibleInstances, OverloadedStrings, RecordWildCards
test-suite doctests
type: exitcode-stdio-1.0
hs-source-dirs: test
main-is: Doctests.hs
default-language: Haskell2010
ghc-options: -dynamic -threaded -j
build-depends: base
, doctest
, QuickCheck
benchmark evaluation benchmark evaluation
hs-source-dirs: bench hs-source-dirs: bench
type: exitcode-stdio-1.0 type: exitcode-stdio-1.0

View File

@ -8,8 +8,6 @@ module Analysis.Abstract.Evaluating
import Control.Abstract.Evaluator import Control.Abstract.Evaluator
import Control.Monad.Effect hiding (run) import Control.Monad.Effect hiding (run)
import Control.Monad.Effect.Fail import Control.Monad.Effect.Fail
import Control.Monad.Effect.Fresh
import Control.Monad.Effect.NonDet
import Control.Monad.Effect.Reader import Control.Monad.Effect.Reader
import Control.Monad.Effect.State import Control.Monad.Effect.State
import Data.Abstract.Configuration import Data.Abstract.Configuration

View File

@ -37,9 +37,7 @@
-- --
-- Assignments can represent alternatives as either committed or uncommitted choices, both written with '<|>'. “Committed” in this context means that a failure in one of the alternatives will not result in backtracking followed by an attempt of one of the other alternatives; thus, committed choice is more efficient. (By the same token, it enables much better error messages since backtracking erases most of the relevant context.) Committed choices are constructed via the following rules: -- Assignments can represent alternatives as either committed or uncommitted choices, both written with '<|>'. “Committed” in this context means that a failure in one of the alternatives will not result in backtracking followed by an attempt of one of the other alternatives; thus, committed choice is more efficient. (By the same token, it enables much better error messages since backtracking erases most of the relevant context.) Committed choices are constructed via the following rules:
-- --
-- 1. 'empty' is dropped from choices: -- 1. 'empty' is dropped from choices.
-- prop> empty <|> a = a -- empty is the left-identity of <|>
-- prop> a <|> empty = a -- empty is the right-identity of <|>
-- --
-- 2. 'symbol' rules construct a committed choice (with only a single alternative). -- 2. 'symbol' rules construct a committed choice (with only a single alternative).
-- --

View File

@ -14,10 +14,10 @@ module Control.Abstract.Analysis
import Control.Abstract.Evaluator as X import Control.Abstract.Evaluator as X
import Control.Effect as X import Control.Effect as X
import Control.Effect.Fresh as X
import Control.Effect.NonDet as X
import qualified Control.Monad.Effect as Effect import qualified Control.Monad.Effect as Effect
import Control.Monad.Effect.Fail as X import Control.Monad.Effect.Fail as X
import Control.Monad.Effect.Fresh as X
import Control.Monad.Effect.NonDet as X
import Control.Monad.Effect.Reader as X import Control.Monad.Effect.Reader as X
import Control.Monad.Effect.State as X import Control.Monad.Effect.State as X
import Data.Abstract.Environment import Data.Abstract.Environment

View File

@ -80,7 +80,7 @@ class (Monad m, Show value) => MonadValue value m where
-- | Construct an array of zero or more values. -- | Construct an array of zero or more values.
array :: [value] -> m value array :: [value] -> m value
-- | Extract a 'ByteString' from a given value. -- | Extract a 'ByteString' from a given value.
asString :: value -> m ByteString asString :: value -> m ByteString
-- | Eliminate boolean values. TODO: s/boolean/truthy -- | Eliminate boolean values. TODO: s/boolean/truthy
@ -101,10 +101,10 @@ toBool :: MonadValue value m => value -> m Bool
toBool v = ifthenelse v (pure True) (pure False) toBool v = ifthenelse v (pure True) (pure False)
forLoop :: (MonadEnvironment value m, MonadValue value m) forLoop :: (MonadEnvironment value m, MonadValue value m)
=> m value -- | Initial statement => m value -- ^ Initial statement
-> m value -- | Condition -> m value -- ^ Condition
-> m value -- | Increment/stepper -> m value -- ^ Increment/stepper
-> m value -- | Body -> m value -- ^ Body
-> m value -> m value
forLoop initial cond step body = do forLoop initial cond step body = do
void initial void initial

View File

@ -1,5 +1,5 @@
{-# LANGUAGE GADTs, MultiParamTypeClasses, TypeOperators, UndecidableInstances #-} {-# LANGUAGE GADTs, MultiParamTypeClasses, TypeOperators, UndecidableInstances #-}
module Control.Monad.Effect.Fresh where module Control.Effect.Fresh where
import Control.Effect import Control.Effect
import Control.Monad.Effect.Internal import Control.Monad.Effect.Internal

View File

@ -1,5 +1,5 @@
{-# LANGUAGE TypeFamilies, TypeOperators, UndecidableInstances #-} {-# LANGUAGE TypeFamilies, TypeOperators, UndecidableInstances #-}
module Control.Monad.Effect.NonDet module Control.Effect.NonDet
( MonadNonDet(..) ( MonadNonDet(..)
, NonDetEff , NonDetEff
) where ) where

View File

@ -36,6 +36,13 @@ subtractRange range1 range2 = Range (start range1) (end range1 - rangeLength (Ra
-- Instances -- Instances
-- $setup
-- >>> import Test.QuickCheck
-- >>> instance Arbitrary Range where arbitrary = Range <$> arbitrary <*> arbitrary
-- $
-- Associativity:
-- prop> \ a b c -> a <> (b <> c) == (a <> b) <> (c :: Range)
instance Semigroup Range where instance Semigroup Range where
Range start1 end1 <> Range start2 end2 = Range (min start1 start2) (max end1 end2) Range start1 end1 <> Range start2 end2 = Range (min start1 start2) (max end1 end2)

24
test/Doctests.hs Normal file
View File

@ -0,0 +1,24 @@
module Main
( main
) where
import System.Environment
import Test.DocTest
main :: IO ()
main = do
args <- getArgs
doctest (map ("-X" ++) extensions ++ "-isrc" : "--fast" : if null args then ["src"] else args)
extensions :: [String]
extensions =
[ "DeriveFoldable"
, "DeriveFunctor"
, "DeriveGeneric"
, "DeriveTraversable"
, "FlexibleContexts"
, "FlexibleInstances"
, "OverloadedStrings"
, "RecordWildCards"
, "StrictData"
]