mirror of
https://github.com/github/semantic.git
synced 2024-12-26 08:25:19 +03:00
Merge remote-tracking branch 'origin/master' into classes
This commit is contained in:
commit
dd1e1c555d
@ -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
|
||||||
@ -263,8 +263,10 @@ test-suite doctests
|
|||||||
hs-source-dirs: test
|
hs-source-dirs: test
|
||||||
main-is: Doctests.hs
|
main-is: Doctests.hs
|
||||||
default-language: Haskell2010
|
default-language: Haskell2010
|
||||||
|
ghc-options: -dynamic -threaded -j
|
||||||
build-depends: base
|
build-depends: base
|
||||||
, doctest
|
, doctest
|
||||||
|
, QuickCheck
|
||||||
|
|
||||||
benchmark evaluation
|
benchmark evaluation
|
||||||
hs-source-dirs: bench
|
hs-source-dirs: bench
|
||||||
|
@ -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
|
||||||
|
@ -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).
|
||||||
--
|
--
|
||||||
|
@ -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 (Environment)
|
import Data.Abstract.Environment (Environment)
|
||||||
|
@ -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
|
@ -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
|
@ -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)
|
||||||
|
|
||||||
|
@ -59,7 +59,6 @@ instance Eq1 Arithmetic where liftEq = genericLiftEq
|
|||||||
instance Ord1 Arithmetic where liftCompare = genericLiftCompare
|
instance Ord1 Arithmetic where liftCompare = genericLiftCompare
|
||||||
instance Show1 Arithmetic where liftShowsPrec = genericLiftShowsPrec
|
instance Show1 Arithmetic where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
-- TODO: Implement Eval instance for Arithmetic
|
|
||||||
instance Evaluatable Arithmetic where
|
instance Evaluatable Arithmetic where
|
||||||
eval = traverse subtermValue >=> go where
|
eval = traverse subtermValue >=> go where
|
||||||
go (Plus a b) = liftNumeric2 add a b where add = liftReal (+)
|
go (Plus a b) = liftNumeric2 add a b where add = liftReal (+)
|
||||||
@ -70,6 +69,19 @@ instance Evaluatable Arithmetic where
|
|||||||
go (Power a b) = liftNumeric2 liftedExponent a b
|
go (Power a b) = liftNumeric2 liftedExponent a b
|
||||||
go (Negate a) = liftNumeric negate a
|
go (Negate a) = liftNumeric negate a
|
||||||
|
|
||||||
|
-- | Regex matching operators (Ruby's =~ and ~!)
|
||||||
|
data Match a
|
||||||
|
= Matches !a !a
|
||||||
|
| NotMatches !a !a
|
||||||
|
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
||||||
|
|
||||||
|
instance Eq1 Match where liftEq = genericLiftEq
|
||||||
|
instance Ord1 Match where liftCompare = genericLiftCompare
|
||||||
|
instance Show1 Match where liftShowsPrec = genericLiftShowsPrec
|
||||||
|
|
||||||
|
-- TODO: Implement Eval instance for Match
|
||||||
|
instance Evaluatable Match
|
||||||
|
|
||||||
-- | Boolean operators.
|
-- | Boolean operators.
|
||||||
data Boolean a
|
data Boolean a
|
||||||
= Or !a !a
|
= Or !a !a
|
||||||
|
@ -36,6 +36,7 @@ type Syntax = '[
|
|||||||
, Expression.Call
|
, Expression.Call
|
||||||
, Expression.Comparison
|
, Expression.Comparison
|
||||||
, Expression.Enumeration
|
, Expression.Enumeration
|
||||||
|
, Expression.Match
|
||||||
, Expression.MemberAccess
|
, Expression.MemberAccess
|
||||||
, Expression.ScopeResolution
|
, Expression.ScopeResolution
|
||||||
, Expression.Subscript
|
, Expression.Subscript
|
||||||
@ -368,7 +369,6 @@ unary = symbol Unary >>= \ location ->
|
|||||||
<|> children ( symbol AnonPlus *> expression )
|
<|> children ( symbol AnonPlus *> expression )
|
||||||
|
|
||||||
-- TODO: Distinguish `===` from `==` ?
|
-- TODO: Distinguish `===` from `==` ?
|
||||||
-- TODO: Distinuish `=~` and `!~` ?
|
|
||||||
binary :: Assignment
|
binary :: Assignment
|
||||||
binary = makeTerm' <$> symbol Binary <*> children (infixTerm expression expression
|
binary = makeTerm' <$> symbol Binary <*> children (infixTerm expression expression
|
||||||
[ (inj .) . Expression.Plus <$ symbol AnonPlus
|
[ (inj .) . Expression.Plus <$ symbol AnonPlus
|
||||||
@ -382,8 +382,8 @@ binary = makeTerm' <$> symbol Binary <*> children (infixTerm expression expressi
|
|||||||
, (inj .) . Expression.Or <$ (symbol AnonOr <|> symbol AnonPipePipe)
|
, (inj .) . Expression.Or <$ (symbol AnonOr <|> symbol AnonPipePipe)
|
||||||
, (inj .) . Expression.BOr <$ symbol AnonPipe
|
, (inj .) . Expression.BOr <$ symbol AnonPipe
|
||||||
, (inj .) . Expression.BXOr <$ symbol AnonCaret
|
, (inj .) . Expression.BXOr <$ symbol AnonCaret
|
||||||
, (inj .) . Expression.Equal <$ (symbol AnonEqualEqual <|> symbol AnonEqualEqualEqual <|> symbol AnonEqualTilde)
|
, (inj .) . Expression.Equal <$ (symbol AnonEqualEqual <|> symbol AnonEqualEqualEqual)
|
||||||
, (inj .) . invert Expression.Equal <$ (symbol AnonBangEqual <|> symbol AnonBangTilde)
|
, (inj .) . invert Expression.Equal <$ symbol AnonBangEqual
|
||||||
, (inj .) . Expression.LShift <$ symbol AnonLAngleLAngle
|
, (inj .) . Expression.LShift <$ symbol AnonLAngleLAngle
|
||||||
, (inj .) . Expression.RShift <$ symbol AnonRAngleRAngle
|
, (inj .) . Expression.RShift <$ symbol AnonRAngleRAngle
|
||||||
, (inj .) . Expression.Comparison <$ symbol AnonLAngleEqualRAngle
|
, (inj .) . Expression.Comparison <$ symbol AnonLAngleEqualRAngle
|
||||||
@ -391,6 +391,8 @@ binary = makeTerm' <$> symbol Binary <*> children (infixTerm expression expressi
|
|||||||
, (inj .) . Expression.GreaterThan <$ symbol AnonRAngle
|
, (inj .) . Expression.GreaterThan <$ symbol AnonRAngle
|
||||||
, (inj .) . Expression.LessThanEqual <$ symbol AnonLAngleEqual
|
, (inj .) . Expression.LessThanEqual <$ symbol AnonLAngleEqual
|
||||||
, (inj .) . Expression.GreaterThanEqual <$ symbol AnonRAngleEqual
|
, (inj .) . Expression.GreaterThanEqual <$ symbol AnonRAngleEqual
|
||||||
|
, (inj .) . Expression.Matches <$ symbol AnonEqualTilde
|
||||||
|
, (inj .) . Expression.NotMatches <$ symbol AnonBangTilde
|
||||||
])
|
])
|
||||||
where invert cons a b = Expression.Not (makeTerm1 (cons a b))
|
where invert cons a b = Expression.Not (makeTerm1 (cons a b))
|
||||||
|
|
||||||
|
@ -6,10 +6,9 @@ import System.Environment
|
|||||||
import Test.DocTest
|
import Test.DocTest
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = getArgs >>= run
|
main = do
|
||||||
|
args <- getArgs
|
||||||
run :: [String] -> IO ()
|
doctest (map ("-X" ++) extensions ++ "-isrc" : "--fast" : if null args then ["src"] else args)
|
||||||
run args = doctest (map ("-X" ++) extensions ++ args ++ ["-isrc"] ++ sources)
|
|
||||||
|
|
||||||
extensions :: [String]
|
extensions :: [String]
|
||||||
extensions =
|
extensions =
|
||||||
@ -23,8 +22,3 @@ extensions =
|
|||||||
, "RecordWildCards"
|
, "RecordWildCards"
|
||||||
, "StrictData"
|
, "StrictData"
|
||||||
]
|
]
|
||||||
|
|
||||||
sources :: [String]
|
|
||||||
sources =
|
|
||||||
[ "src/Data/Abstract/Environment.hs"
|
|
||||||
]
|
|
||||||
|
@ -1,14 +1,16 @@
|
|||||||
(Program
|
(Program
|
||||||
{+(Comparison
|
{(Equal
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(Identifier)-})
|
||||||
|
->(Comparison
|
||||||
|
{+(Identifier)+}
|
||||||
|
{+(Identifier)+}) }
|
||||||
|
{+(Matches
|
||||||
{+(Identifier)+}
|
{+(Identifier)+}
|
||||||
{+(Identifier)+})+}
|
{+(Identifier)+})+}
|
||||||
(Equal
|
|
||||||
(Identifier)
|
|
||||||
(Identifier))
|
|
||||||
{+(Assignment
|
{+(Assignment
|
||||||
{+(Identifier)+}
|
{+(Identifier)+}
|
||||||
{+(Not
|
{+(Not{+(Identifier)+})+})+}
|
||||||
{+(Identifier)+})+})+}
|
|
||||||
{-(Not
|
{-(Not
|
||||||
{-(Equal
|
{-(Equal
|
||||||
{-(Identifier)-}
|
{-(Identifier)-}
|
||||||
|
@ -1,10 +1,10 @@
|
|||||||
(Program
|
(Program
|
||||||
{-(Comparison
|
{(Comparison
|
||||||
{-(Identifier)-}
|
{-(Identifier)-}
|
||||||
{-(Identifier)-})-}
|
{-(Identifier)-})
|
||||||
(Equal
|
->(Equal
|
||||||
(Identifier)
|
{+(Identifier)+}
|
||||||
(Identifier))
|
{+(Identifier)+}) }
|
||||||
{+(Not
|
{+(Not
|
||||||
{+(Equal
|
{+(Equal
|
||||||
{+(Identifier)+}
|
{+(Identifier)+}
|
||||||
@ -12,7 +12,9 @@
|
|||||||
{+(Equal
|
{+(Equal
|
||||||
{+(Identifier)+}
|
{+(Identifier)+}
|
||||||
{+(Identifier)+})+}
|
{+(Identifier)+})+}
|
||||||
|
{-(Matches
|
||||||
|
{-(Identifier)-}
|
||||||
|
{-(Identifier)-})-}
|
||||||
{-(Assignment
|
{-(Assignment
|
||||||
{-(Identifier)-}
|
{-(Identifier)-}
|
||||||
{-(Not
|
{-(Not{-(Identifier)-})-})- })
|
||||||
{-(Identifier)-})-})-})
|
|
||||||
|
@ -2,7 +2,7 @@
|
|||||||
(Comparison
|
(Comparison
|
||||||
(Identifier)
|
(Identifier)
|
||||||
(Identifier))
|
(Identifier))
|
||||||
(Equal
|
(Matches
|
||||||
(Identifier)
|
(Identifier)
|
||||||
(Identifier))
|
(Identifier))
|
||||||
(Assignment
|
(Assignment
|
||||||
|
Loading…
Reference in New Issue
Block a user