From 1499a2591a4a136a31f4439664b73f31807a9f50 Mon Sep 17 00:00:00 2001 From: Patrick Thomson Date: Mon, 5 Mar 2018 15:25:18 -0500 Subject: [PATCH 01/16] Initial changes to support evaluating Go snippets --- src/Data/Syntax/Declaration.hs | 17 ++++++- src/Language/Go/Syntax.hs | 86 +++++++++++++++++++++++++++------- src/Language/Go/Type.hs | 16 +++++-- src/Semantic/Util.hs | 5 ++ 4 files changed, 102 insertions(+), 22 deletions(-) diff --git a/src/Data/Syntax/Declaration.hs b/src/Data/Syntax/Declaration.hs index bdf639ef7..1f6721529 100644 --- a/src/Data/Syntax/Declaration.hs +++ b/src/Data/Syntax/Declaration.hs @@ -156,8 +156,21 @@ instance Eq1 Module where liftEq = genericLiftEq instance Ord1 Module where liftCompare = genericLiftCompare instance Show1 Module where liftShowsPrec = genericLiftShowsPrec --- TODO: Implement Eval instance for Module -instance Evaluatable Module +-- TODO: Fix this extremely bogus instance (copied from that of Program) +-- In Go, functions in the same module can be spread across files. +-- We need to ensure that all input files have aggregated their content into +-- a coherent module before we begin evaluating a module. +instance Evaluatable Module where + eval (Module _ xs) = eval' xs + where + interface val = pure val -- inj . Value.Interface val <$> askLocalEnv + + eval' [] = unit >>= interface + eval' [x] = subtermValue x >>= interface + eval' (x:xs) = do + _ <- subtermValue x + env <- getGlobalEnv + localEnv (envUnion env) (eval' xs) -- | A decorator in Python data Decorator a = Decorator { decoratorIdentifier :: !a, decoratorParamaters :: ![a], decoratorBody :: !a } diff --git a/src/Language/Go/Syntax.hs b/src/Language/Go/Syntax.hs index c4550cd06..904cbb2b1 100644 --- a/src/Language/Go/Syntax.hs +++ b/src/Language/Go/Syntax.hs @@ -2,51 +2,70 @@ module Language.Go.Syntax where import Prologue +import Data.Abstract.Evaluatable import Diffing.Algorithm -- A composite literal in Go data Composite a = Composite { compositeType :: !a, compositeElement :: !a } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) instance Eq1 Composite where liftEq = genericLiftEq instance Ord1 Composite where liftCompare = genericLiftCompare instance Show1 Composite where liftShowsPrec = genericLiftShowsPrec +-- TODO: Implement Eval instance for Composite +instance Evaluatable Composite + -- | A default pattern in a Go select or switch statement (e.g. `switch { default: s() }`). newtype DefaultPattern a = DefaultPattern { defaultPatternBody :: a } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) instance Eq1 DefaultPattern where liftEq = genericLiftEq instance Ord1 DefaultPattern where liftCompare = genericLiftCompare instance Show1 DefaultPattern where liftShowsPrec = genericLiftShowsPrec +-- TODO: Implement Eval instance for DefaultPattern +instance Evaluatable DefaultPattern + -- | A defer statement in Go (e.g. `defer x()`). newtype Defer a = Defer { deferBody :: a } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) instance Eq1 Defer where liftEq = genericLiftEq instance Ord1 Defer where liftCompare = genericLiftCompare instance Show1 Defer where liftShowsPrec = genericLiftShowsPrec +-- TODO: Implement Eval instance for Defer +instance Evaluatable Defer + -- | A go statement (i.e. go routine) in Go (e.g. `go x()`). newtype Go a = Go { goBody :: a } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) instance Eq1 Go where liftEq = genericLiftEq instance Ord1 Go where liftCompare = genericLiftCompare instance Show1 Go where liftShowsPrec = genericLiftShowsPrec +-- TODO: Implement Eval instance for Go +instance Evaluatable Go + -- | A label statement in Go (e.g. `label:continue`). data Label a = Label { _labelName :: !a, labelStatement :: !a } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) instance Eq1 Label where liftEq = genericLiftEq instance Ord1 Label where liftCompare = genericLiftCompare instance Show1 Label where liftShowsPrec = genericLiftShowsPrec +-- TODO: Implement Eval instance for Label +instance Evaluatable Label + -- | A rune literal in Go (e.g. `'⌘'`). newtype Rune a = Rune { _runeLiteral :: ByteString } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + +-- TODO: Implement Eval instance for Rune +instance Evaluatable Rune instance Eq1 Rune where liftEq = genericLiftEq instance Ord1 Rune where liftCompare = genericLiftCompare @@ -54,7 +73,10 @@ instance Show1 Rune where liftShowsPrec = genericLiftShowsPrec -- | A select statement in Go (e.g. `select { case x := <-c: x() }` where each case is a send or receive operation on channels). data Select a = Select { selectCases :: !a } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + +-- TODO: Implement Eval instance for Select +instance Evaluatable Select instance Eq1 Select where liftEq = genericLiftEq instance Ord1 Select where liftCompare = genericLiftCompare @@ -62,80 +84,110 @@ instance Show1 Select where liftShowsPrec = genericLiftShowsPrec -- | A send statement in Go (e.g. `channel <- value`). data Send a = Send { sendReceiver :: !a, sendValue :: !a } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) instance Eq1 Send where liftEq = genericLiftEq instance Ord1 Send where liftCompare = genericLiftCompare instance Show1 Send where liftShowsPrec = genericLiftShowsPrec +-- TODO: Implement Eval instance for Send +instance Evaluatable Send + -- | A slice expression in Go (e.g. `a[1:4:3]` where a is a list, 1 is the low bound, 4 is the high bound, and 3 is the max capacity). data Slice a = Slice { sliceName :: !a, sliceLow :: !a, sliceHigh :: !a, sliceCapacity :: !a } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) instance Eq1 Slice where liftEq = genericLiftEq instance Ord1 Slice where liftCompare = genericLiftCompare instance Show1 Slice where liftShowsPrec = genericLiftShowsPrec +-- TODO: Implement Eval instance for Slice +instance Evaluatable Slice + -- | A type switch statement in Go (e.g. `switch x.(type) { // cases }`). data TypeSwitch a = TypeSwitch { typeSwitchSubject :: !a, typeSwitchCases :: !a } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) instance Eq1 TypeSwitch where liftEq = genericLiftEq instance Ord1 TypeSwitch where liftCompare = genericLiftCompare instance Show1 TypeSwitch where liftShowsPrec = genericLiftShowsPrec +-- TODO: Implement Eval instance for TypeSwitch +instance Evaluatable TypeSwitch + -- | A type switch guard statement in a Go type switch statement (e.g. `switch i := x.(type) { // cases}`). newtype TypeSwitchGuard a = TypeSwitchGuard { typeSwitchGuardSubject :: a } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) instance Eq1 TypeSwitchGuard where liftEq = genericLiftEq instance Ord1 TypeSwitchGuard where liftCompare = genericLiftCompare instance Show1 TypeSwitchGuard where liftShowsPrec = genericLiftShowsPrec +-- TODO: Implement Eval instance for TypeSwitchGuard +instance Evaluatable TypeSwitchGuard + -- | A receive statement in a Go select statement (e.g. `case value := <-channel` ) data Receive a = Receive { receiveSubject :: !a, receiveExpression :: !a } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) instance Eq1 Receive where liftEq = genericLiftEq instance Ord1 Receive where liftCompare = genericLiftCompare instance Show1 Receive where liftShowsPrec = genericLiftShowsPrec +-- TODO: Implement Eval instance for Receive +instance Evaluatable Receive + -- | A receive operator unary expression in Go (e.g. `<-channel` ) data ReceiveOperator a = ReceiveOperator a - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) instance Eq1 ReceiveOperator where liftEq = genericLiftEq instance Ord1 ReceiveOperator where liftCompare = genericLiftCompare instance Show1 ReceiveOperator where liftShowsPrec = genericLiftShowsPrec +-- TODO: Implement Eval instance for ReceiveOperator +instance Evaluatable ReceiveOperator + -- | A field declaration in a Go struct type declaration. data Field a = Field { fieldContext :: ![a], fieldName :: !a } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) instance Eq1 Field where liftEq = genericLiftEq instance Ord1 Field where liftCompare = genericLiftCompare instance Show1 Field where liftShowsPrec = genericLiftShowsPrec +-- TODO: Implement Eval instance for Field +instance Evaluatable Field + -- | A type assertion in Go (e.g. `x.(T)` where the value of `x` is not nil and is of type `T`). data TypeAssertion a = TypeAssertion { typeAssertionSubject :: !a, typeAssertionType :: !a } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) instance Eq1 TypeAssertion where liftEq = genericLiftEq instance Ord1 TypeAssertion where liftCompare = genericLiftCompare instance Show1 TypeAssertion where liftShowsPrec = genericLiftShowsPrec +-- TODO: Implement Eval instance for TypeAssertion +instance Evaluatable TypeAssertion + -- | A type conversion expression in Go (e.g. `T(x)` where `T` is a type and `x` is an expression that can be converted to type `T`). data TypeConversion a = TypeConversion { typeConversionType :: !a, typeConversionSubject :: !a } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) instance Eq1 TypeConversion where liftEq = genericLiftEq instance Ord1 TypeConversion where liftCompare = genericLiftCompare instance Show1 TypeConversion where liftShowsPrec = genericLiftShowsPrec +-- TODO: Implement Eval instance for TypeConversion +instance Evaluatable TypeConversion + -- | Variadic arguments and parameters in Go (e.g. parameter: `param ...Type`, argument: `Type...`). data Variadic a = Variadic { variadicContext :: [a], variadicIdentifier :: a } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) instance Eq1 Variadic where liftEq = genericLiftEq instance Ord1 Variadic where liftCompare = genericLiftCompare instance Show1 Variadic where liftShowsPrec = genericLiftShowsPrec + +-- TODO: Implement Eval instance for Variadic +instance Evaluatable Variadic diff --git a/src/Language/Go/Type.hs b/src/Language/Go/Type.hs index f867030ee..b6292c5c0 100644 --- a/src/Language/Go/Type.hs +++ b/src/Language/Go/Type.hs @@ -2,28 +2,38 @@ module Language.Go.Type where import Prologue +import Data.Abstract.Evaluatable import Diffing.Algorithm -- | A Bidirectional channel in Go (e.g. `chan`). newtype BidirectionalChannel a = BidirectionalChannel a - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) instance Eq1 BidirectionalChannel where liftEq = genericLiftEq instance Ord1 BidirectionalChannel where liftCompare = genericLiftCompare instance Show1 BidirectionalChannel where liftShowsPrec = genericLiftShowsPrec +-- TODO: Implement Eval instance for BidirectionalChannel +instance Evaluatable BidirectionalChannel + -- | A Receive channel in Go (e.g. `<-chan`). newtype ReceiveChannel a = ReceiveChannel a - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) instance Eq1 ReceiveChannel where liftEq = genericLiftEq instance Ord1 ReceiveChannel where liftCompare = genericLiftCompare instance Show1 ReceiveChannel where liftShowsPrec = genericLiftShowsPrec +-- TODO: Implement Eval instance for ReceiveChannel +instance Evaluatable ReceiveChannel + -- | A Send channel in Go (e.g. `chan<-`). newtype SendChannel a = SendChannel a - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) instance Eq1 SendChannel where liftEq = genericLiftEq instance Ord1 SendChannel where liftCompare = genericLiftCompare instance Show1 SendChannel where liftShowsPrec = genericLiftShowsPrec + +-- TODO: Implement Eval instance for SendChannel +instance Evaluatable SendChannel diff --git a/src/Semantic/Util.hs b/src/Semantic/Util.hs index aae481164..029b23078 100644 --- a/src/Semantic/Util.hs +++ b/src/Semantic/Util.hs @@ -22,9 +22,11 @@ import Semantic import Semantic.IO as IO import Semantic.Task +import qualified Language.Go.Assignment as Go import qualified Language.Ruby.Assignment as Ruby import qualified Language.Python.Assignment as Python +type GoValue = Value Precise (Term (Union Go.Syntax) (Record Location)) type RubyValue = Value Precise (Term (Union Ruby.Syntax) (Record Location)) type PythonValue = Value Precise (Term (Union Python.Syntax) (Record Location)) @@ -40,6 +42,9 @@ evaluateRubyFiles paths = do (t:ts) <- runTask $ traverse (parse rubyParser) blobs pure $ evaluates @RubyValue (zip bs ts) (b, t) +-- Go +evaluateGoFile path = evaluate @GoValue <$> + (file path >>= runTask . parse goParser) -- Python evaluatePythonFile path = evaluate @PythonValue <$> From b2e5297d9fa2c3880afb474ab0bd4bf0c198053f Mon Sep 17 00:00:00 2001 From: Patrick Thomson Date: Tue, 6 Mar 2018 15:44:15 -0500 Subject: [PATCH 02/16] use the shiny new evaluateCache --- src/Semantic/Util.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Semantic/Util.hs b/src/Semantic/Util.hs index b045dffa1..72818d32b 100644 --- a/src/Semantic/Util.hs +++ b/src/Semantic/Util.hs @@ -45,7 +45,7 @@ evaluateRubyFiles paths = do pure $ evaluates @RubyValue (zip bs ts) (b, t) -- Go -typecheckGoFile path = evaluate @GoValue <$> +typecheckGoFile path = evaluateCache @Type <$> (file path >>= runTask . parse goParser) -- Python From 189a33c16bde0463da05a8c3f1360f7a9ba95bca Mon Sep 17 00:00:00 2001 From: Patrick Thomson Date: Wed, 7 Mar 2018 15:16:59 -0500 Subject: [PATCH 03/16] use ModuleTable --- src/Analysis/Abstract/Caching.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Analysis/Abstract/Caching.hs b/src/Analysis/Abstract/Caching.hs index 0c44c4fe6..726bafb3d 100644 --- a/src/Analysis/Abstract/Caching.hs +++ b/src/Analysis/Abstract/Caching.hs @@ -17,7 +17,7 @@ import Data.Abstract.Cache import Data.Abstract.Configuration import Data.Abstract.Environment import Data.Abstract.Evaluatable -import Data.Abstract.Linker +import Data.Abstract.ModuleTable import Data.Abstract.Live import Data.Abstract.Store import Data.Abstract.Value @@ -34,8 +34,8 @@ type CachingEffects t v , State (Store (LocationFor v) v) -- For 'MonadStore'. , Reader (Cache (LocationFor v) t v) -- For 'MonadCacheIn'. , State (Cache (LocationFor v) t v) -- For 'MonadCacheOut'. - , Reader (Linker t) -- Cache of unevaluated modules - , State (Linker v) -- Cache of evaluated modules + , Reader (ModuleTable t) -- Cache of unevaluated modules + , State (ModuleTable v) -- Cache of evaluated modules ] newtype CachingAnalysis term value a = CachingAnalysis { runCachingAnalysis :: Evaluator (CachingEffects term value) term value a } From 0ac705b0f5b6bb0f857e7eba9c5fecc677d02233 Mon Sep 17 00:00:00 2001 From: Patrick Thomson Date: Wed, 7 Mar 2018 19:34:20 -0500 Subject: [PATCH 04/16] flesh out some benchmarks --- bench/Main.hs | 18 ++++++++++++++++++ .../python/function-definition.py | 14 ++++++++++++++ .../python/if-statement-functions.py | 12 ++++++++++++ .../bench-fixtures/python/simple-assignment.py | 5 +++++ semantic.cabal | 12 ++++++++++++ test/fixtures/python/assignment.A.py | 2 -- 6 files changed, 61 insertions(+), 2 deletions(-) create mode 100644 bench/Main.hs create mode 100644 bench/bench-fixtures/python/function-definition.py create mode 100644 bench/bench-fixtures/python/if-statement-functions.py create mode 100644 bench/bench-fixtures/python/simple-assignment.py diff --git a/bench/Main.hs b/bench/Main.hs new file mode 100644 index 000000000..9de07b849 --- /dev/null +++ b/bench/Main.hs @@ -0,0 +1,18 @@ +module Main where + +import Criterion.Main +import Semantic.Util +import Data.Monoid + +pyEval :: FilePath -> Benchmarkable +pyEval = whnfIO . evaluatePythonFile . ("bench/bench-fixtures/python/" <>) + + + +main :: IO () +main = defaultMain [ + bgroup "python" [ bench "assignment" $ pyEval "simple-assignment.py" + , bench "function def" $ pyEval "function-definition.py" + , bench "if + function calls" $ pyEval "if-statement-functions.py" + ] + ] diff --git a/bench/bench-fixtures/python/function-definition.py b/bench/bench-fixtures/python/function-definition.py new file mode 100644 index 000000000..d86662294 --- /dev/null +++ b/bench/bench-fixtures/python/function-definition.py @@ -0,0 +1,14 @@ +def a(): + b + +def c(d): + e + +def g(g, *h,): + i + +def h(i=j): + i + +def i(j:str="default", **c): + j diff --git a/bench/bench-fixtures/python/if-statement-functions.py b/bench/bench-fixtures/python/if-statement-functions.py new file mode 100644 index 000000000..be76ccf2f --- /dev/null +++ b/bench/bench-fixtures/python/if-statement-functions.py @@ -0,0 +1,12 @@ +def foo(): return "bipp" + +def bar(): return foo() + +def baz(): return baz() + +def why(): return "elle" + +if True: + foo() +else: + why() diff --git a/bench/bench-fixtures/python/simple-assignment.py b/bench/bench-fixtures/python/simple-assignment.py new file mode 100644 index 000000000..d3c54e12d --- /dev/null +++ b/bench/bench-fixtures/python/simple-assignment.py @@ -0,0 +1,5 @@ +foo = 2 +bar = foo +dang = 3 +song = dang +song diff --git a/semantic.cabal b/semantic.cabal index a30c3bb12..5fd406214 100644 --- a/semantic.cabal +++ b/semantic.cabal @@ -251,6 +251,18 @@ test-suite test default-language: Haskell2010 default-extensions: DeriveFunctor, DeriveGeneric, FlexibleContexts, FlexibleInstances, OverloadedStrings, RecordWildCards +benchmark evaluation + hs-source-dirs: bench + type: exitcode-stdio-1.0 + main-is: Main.hs + ghc-options: -threaded -rtsopts "-with-rtsopts=-N -A4m -n2m" -static -j -O + cc-options: -DU_STATIC_IMPLEMENTATION=1 + cpp-options: -DU_STATIC_IMPLEMENTATION=1 + build-depends: base + , criterion + , semantic + + source-repository head type: git location: https://github.com/github/semantic diff --git a/test/fixtures/python/assignment.A.py b/test/fixtures/python/assignment.A.py index 36cac3d91..1337a530c 100644 --- a/test/fixtures/python/assignment.A.py +++ b/test/fixtures/python/assignment.A.py @@ -1,3 +1 @@ a = 1 -a, b = 1, 2 -a, = 1, 2 From be2d90f0290296e4022ce6ab3406813ba067f40c Mon Sep 17 00:00:00 2001 From: Patrick Thomson Date: Wed, 7 Mar 2018 19:47:23 -0500 Subject: [PATCH 05/16] add ruby --- bench/Main.hs | 11 +++++++--- .../python/function-definition.py | 6 +++--- .../python/if-statement-functions.py | 4 ++-- .../ruby/function-definition.rb | 19 +++++++++++++++++ .../ruby/if-statement-functions.rb | 21 +++++++++++++++++++ .../bench-fixtures/ruby/simple-assignment.rb | 5 +++++ 6 files changed, 58 insertions(+), 8 deletions(-) create mode 100644 bench/bench-fixtures/ruby/function-definition.rb create mode 100644 bench/bench-fixtures/ruby/if-statement-functions.rb create mode 100644 bench/bench-fixtures/ruby/simple-assignment.rb diff --git a/bench/Main.hs b/bench/Main.hs index 9de07b849..774faeaef 100644 --- a/bench/Main.hs +++ b/bench/Main.hs @@ -7,12 +7,17 @@ import Data.Monoid pyEval :: FilePath -> Benchmarkable pyEval = whnfIO . evaluatePythonFile . ("bench/bench-fixtures/python/" <>) - +rbEval :: FilePath -> Benchmarkable +rbEval = whnfIO . evaluateRubyFile . ("bench/bench-fixtures/ruby/" <>) main :: IO () -main = defaultMain [ - bgroup "python" [ bench "assignment" $ pyEval "simple-assignment.py" +main = defaultMain + [ bgroup "python" [ bench "assignment" $ pyEval "simple-assignment.py" , bench "function def" $ pyEval "function-definition.py" , bench "if + function calls" $ pyEval "if-statement-functions.py" ] + , bgroup "ruby" [ bench "assignment" $ rbEval "simple-assignment.rb" + , bench "function def" $ rbEval "function-definition.rb" + , bench "if + function calls" $ rbEval "if-statement-functions.rb" + ] ] diff --git a/bench/bench-fixtures/python/function-definition.py b/bench/bench-fixtures/python/function-definition.py index d86662294..5e687baf3 100644 --- a/bench/bench-fixtures/python/function-definition.py +++ b/bench/bench-fixtures/python/function-definition.py @@ -4,11 +4,11 @@ def a(): def c(d): e -def g(g, *h,): +def g(g, *h): i -def h(i=j): +def h(i=1): i -def i(j:str="default", **c): +def i(j="default", **c): j diff --git a/bench/bench-fixtures/python/if-statement-functions.py b/bench/bench-fixtures/python/if-statement-functions.py index be76ccf2f..b0354a090 100644 --- a/bench/bench-fixtures/python/if-statement-functions.py +++ b/bench/bench-fixtures/python/if-statement-functions.py @@ -2,11 +2,11 @@ def foo(): return "bipp" def bar(): return foo() -def baz(): return baz() +def baz(): return bar() def why(): return "elle" if True: - foo() + baz() else: why() diff --git a/bench/bench-fixtures/ruby/function-definition.rb b/bench/bench-fixtures/ruby/function-definition.rb new file mode 100644 index 000000000..275e25082 --- /dev/null +++ b/bench/bench-fixtures/ruby/function-definition.rb @@ -0,0 +1,19 @@ +def a() + "b" +end + +def c(d) + "e" +end + +def g(g_) + "i" +end + +def h(i=1) + i +end + +def i() + "j" +end diff --git a/bench/bench-fixtures/ruby/if-statement-functions.rb b/bench/bench-fixtures/ruby/if-statement-functions.rb new file mode 100644 index 000000000..52f7af32f --- /dev/null +++ b/bench/bench-fixtures/ruby/if-statement-functions.rb @@ -0,0 +1,21 @@ +def foo() + "bipp" +end + +def bar() + foo() +end + +def baz() + bar() +end + +def why() + return "elle" +end + +if true + baz() +else + why() +end diff --git a/bench/bench-fixtures/ruby/simple-assignment.rb b/bench/bench-fixtures/ruby/simple-assignment.rb new file mode 100644 index 000000000..d3c54e12d --- /dev/null +++ b/bench/bench-fixtures/ruby/simple-assignment.rb @@ -0,0 +1,5 @@ +foo = 2 +bar = foo +dang = 3 +song = dang +song From 1ea97534b6d84c20c137db8994fee18306c6f1ee Mon Sep 17 00:00:00 2001 From: Patrick Thomson Date: Wed, 7 Mar 2018 19:56:54 -0500 Subject: [PATCH 06/16] print so that we know everything is evaluated --- bench/Main.hs | 5 +++-- semantic.cabal | 2 +- 2 files changed, 4 insertions(+), 3 deletions(-) diff --git a/bench/Main.hs b/bench/Main.hs index 774faeaef..4a13bfa1f 100644 --- a/bench/Main.hs +++ b/bench/Main.hs @@ -3,12 +3,13 @@ module Main where import Criterion.Main import Semantic.Util import Data.Monoid +import Control.Monad pyEval :: FilePath -> Benchmarkable -pyEval = whnfIO . evaluatePythonFile . ("bench/bench-fixtures/python/" <>) +pyEval = whnfIO . (evaluatePythonFile >=> print) . ("bench/bench-fixtures/python/" <>) rbEval :: FilePath -> Benchmarkable -rbEval = whnfIO . evaluateRubyFile . ("bench/bench-fixtures/ruby/" <>) +rbEval = whnfIO . (evaluateRubyFile >=> print) . ("bench/bench-fixtures/ruby/" <>) main :: IO () main = defaultMain diff --git a/semantic.cabal b/semantic.cabal index 5fd406214..aa6803529 100644 --- a/semantic.cabal +++ b/semantic.cabal @@ -255,7 +255,7 @@ benchmark evaluation hs-source-dirs: bench type: exitcode-stdio-1.0 main-is: Main.hs - ghc-options: -threaded -rtsopts "-with-rtsopts=-N -A4m -n2m" -static -j -O + ghc-options: -threaded -rtsopts "-with-rtsopts=-N -A4m -n2m -T" -static -j -O cc-options: -DU_STATIC_IMPLEMENTATION=1 cpp-options: -DU_STATIC_IMPLEMENTATION=1 build-depends: base From 5ffa873279c30caa02b6fee2797dd5ef74012e68 Mon Sep 17 00:00:00 2001 From: Patrick Thomson Date: Thu, 8 Mar 2018 10:13:26 -0500 Subject: [PATCH 07/16] add script/bench --- bench/Main.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/bench/Main.hs b/bench/Main.hs index 4a13bfa1f..62dffdc7f 100644 --- a/bench/Main.hs +++ b/bench/Main.hs @@ -6,10 +6,10 @@ import Data.Monoid import Control.Monad pyEval :: FilePath -> Benchmarkable -pyEval = whnfIO . (evaluatePythonFile >=> print) . ("bench/bench-fixtures/python/" <>) +pyEval = whnfIO . fmap show . evaluatePythonFile . ("bench/bench-fixtures/python/" <>) rbEval :: FilePath -> Benchmarkable -rbEval = whnfIO . (evaluateRubyFile >=> print) . ("bench/bench-fixtures/ruby/" <>) +rbEval = whnfIO . fmap show . evaluateRubyFile . ("bench/bench-fixtures/ruby/" <>) main :: IO () main = defaultMain From e5d3b0cf69609fafc8734e08da78b6bcff6de382 Mon Sep 17 00:00:00 2001 From: Patrick Thomson Date: Thu, 8 Mar 2018 10:17:32 -0500 Subject: [PATCH 08/16] fix test I munged up --- test/fixtures/python/assignment.A.py | 2 ++ 1 file changed, 2 insertions(+) diff --git a/test/fixtures/python/assignment.A.py b/test/fixtures/python/assignment.A.py index 1337a530c..36cac3d91 100644 --- a/test/fixtures/python/assignment.A.py +++ b/test/fixtures/python/assignment.A.py @@ -1 +1,3 @@ a = 1 +a, b = 1, 2 +a, = 1, 2 From 4378fa5657e4aaf04fb309ff90d7a3377fbd172d Mon Sep 17 00:00:00 2001 From: Patrick Thomson Date: Thu, 8 Mar 2018 13:18:36 -0500 Subject: [PATCH 09/16] add comment --- bench/Main.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/bench/Main.hs b/bench/Main.hs index 62dffdc7f..cf6e76147 100644 --- a/bench/Main.hs +++ b/bench/Main.hs @@ -5,6 +5,11 @@ import Semantic.Util import Data.Monoid import Control.Monad +-- We use `fmap show` to ensure that all the parts of the result of evaluation are +-- evaluated themselves. While an NFData instance is the most morally correct way +-- to do this, I'm reluctant to add NFData instances to every single datatype in the +-- project—coercing the result into a string will suffice, though it throws off the +-- memory allocation results a bit. pyEval :: FilePath -> Benchmarkable pyEval = whnfIO . fmap show . evaluatePythonFile . ("bench/bench-fixtures/python/" <>) From a883bf9adac4a384f2dbf6016d337a6fadd6e4b0 Mon Sep 17 00:00:00 2001 From: Patrick Thomson Date: Fri, 9 Mar 2018 11:11:09 -0500 Subject: [PATCH 10/16] :fire: Control.Monad.Effect.Cache. MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit This interface has already been obsoleted—its only consumer has a private interface for its caching functionality, and @robrix's work will restore a generalized version. No reason to keep this about. --- semantic.cabal | 1 - src/Control/Monad/Effect/Cache.hs | 63 ------------------------------- 2 files changed, 64 deletions(-) delete mode 100644 src/Control/Monad/Effect/Cache.hs diff --git a/semantic.cabal b/semantic.cabal index 662e35303..1f8047d7f 100644 --- a/semantic.cabal +++ b/semantic.cabal @@ -37,7 +37,6 @@ library -- Control flow , Control.Effect -- Effects used for program analysis - , Control.Monad.Effect.Cache , Control.Monad.Effect.Fresh -- , Control.Monad.Effect.GC , Control.Monad.Effect.NonDet diff --git a/src/Control/Monad/Effect/Cache.hs b/src/Control/Monad/Effect/Cache.hs deleted file mode 100644 index 5d72578b9..000000000 --- a/src/Control/Monad/Effect/Cache.hs +++ /dev/null @@ -1,63 +0,0 @@ -{-# LANGUAGE MultiParamTypeClasses, TypeOperators, UndecidableInstances #-} -module Control.Monad.Effect.Cache where - -import Control.Monad.Effect -import Control.Monad.Effect.Reader -import Control.Monad.Effect.State -import Data.Abstract.Cache -import Data.Abstract.Value - --- | 'Monad's offering a readable 'Cache' of values & stores for each configuration in a program. --- --- This (in-)cache is used as an oracle for the results of recursive computations, allowing us to finitize potentially nonterminating control flow by repeatedly computing the results until analysis converges on a stable value. Each iteration of this process must consult this cache only _after_ evaluating the configuration itself in order to ensure soundness (since it could otherwise produce stale results for some configurations). --- --- Since finitization crucially depends on convergence, this cache should only be used with value abstractions that will converge for multiple disjoint assignments of a given variable, e.g. its type, and not with precisely-modelled values. To illustrate why, consider a simple incrementing recursive function: --- --- > inc :: Integer -> a --- > inc n = inc (n + 1) --- --- @n@ differs at every iteration, and thus a precise modelling of the integral value will not converge in the store: each iteration will allocate a new address & write a distinct value into it. Modelling values with their types _will_ converge, however, as the type at each iteration is the same. -class Monad m => MonadCacheIn t v m where - -- | Retrieve the local in-cache. - askCache :: m (Cache (LocationFor v) t v) - - -- | Run a computation with a locally-modified in-cache. - localCache :: (Cache (LocationFor v) t v -> Cache (LocationFor v) t v) -> m a -> m a - -instance (Reader (Cache (LocationFor v) t v) :< fs) => MonadCacheIn t v (Eff fs) where - askCache = ask - localCache = local - --- | Project a value out of the in-cache. -asksCache :: MonadCacheIn t v m => (Cache (LocationFor v) t v -> a) -> m a -asksCache f = f <$> askCache - - --- | 'Monad's offering a readable & writable 'Cache' of values & stores for each configuration in a program. --- --- This (out-)cache is used to store the results of recursive computations, allowing us to finitize each iteration of an analysis by first looking up the current configuration in the cache and only evaluating: --- --- 1. If the configuration has not been visited before, and --- 2. _after_ copying the previous iteration’s results (from the in-cache, and defaulting to a 'mempty' set of results) into the out-cache. --- --- Thus, visiting the same configuration twice recursively will terminate, since we’ll have consulted the in-cache as an oracle before evaluating, and after evaluating, the resulting value and store should be appended into the out-cache. Then, once the current iteration of the analysis has completed, the updated out-cache will be used as the oracle for the next iteration, until such time as the cache converges. --- --- See also 'MonadCacheIn' for discussion of the conditions of finitization. -class Monad m => MonadCacheOut t v m where - -- | Retrieve the current out-cache. - getCache :: m (Cache (LocationFor v) t v) - - -- | Update the current out-cache. - putCache :: Cache (LocationFor v) t v -> m () - -instance (State (Cache (LocationFor v) t v) :< fs) => MonadCacheOut t v (Eff fs) where - getCache = get - putCache = put - --- | Project a value out of the out-cache. -getsCache :: MonadCacheOut t v m => (Cache (LocationFor v) t v -> a) -> m a -getsCache f = f <$> getCache - --- | Modify the current out-cache using a given function. -modifyCache :: MonadCacheOut t v m => (Cache (LocationFor v) t v -> Cache (LocationFor v) t v) -> m () -modifyCache f = fmap f getCache >>= putCache From 2e3c1d0715943cb456ac415e6025578cf1d71a5c Mon Sep 17 00:00:00 2001 From: Patrick Thomson Date: Fri, 9 Mar 2018 11:36:37 -0500 Subject: [PATCH 11/16] Remove references to obsolete identifiers. --- src/Analysis/Abstract/Caching.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Analysis/Abstract/Caching.hs b/src/Analysis/Abstract/Caching.hs index ee853ce8a..30d0b5cee 100644 --- a/src/Analysis/Abstract/Caching.hs +++ b/src/Analysis/Abstract/Caching.hs @@ -32,8 +32,8 @@ type CachingEffects t v , Fail -- For 'MonadFail'. , NonDetEff -- For 'Alternative' & 'MonadNonDet'. , State (Store (LocationFor v) v) -- For 'MonadStore'. - , Reader (Cache (LocationFor v) t v) -- For 'MonadCacheIn'. - , State (Cache (LocationFor v) t v) -- For 'MonadCacheOut'. + , Reader (Cache (LocationFor v) t v) -- For reading memoized values. + , State (Cache (LocationFor v) t v) -- For writing said values. , Reader (ModuleTable t) -- Cache of unevaluated modules , State (ModuleTable (EnvironmentFor v)) -- Cache of evaluated modules ] From da2a3fc7a8dd04b4ecf286b1bb7f846e74935cc4 Mon Sep 17 00:00:00 2001 From: Patrick Thomson Date: Fri, 9 Mar 2018 12:07:34 -0500 Subject: [PATCH 12/16] Initial pass fixing errors raised by `weeder`. This fixes a lot of unnecessary exports in the specs, removes a couple otiose imports (comonads and semigroups are provided by base, I beleive), and removes a duplicated function. --- semantic.cabal | 2 -- test/Assigning/Assignment/Spec.hs | 2 +- test/Data/Functor/Classes/Generic/Spec.hs | 2 +- test/Data/Mergeable/Spec.hs | 2 +- test/Data/Source/Spec.hs | 2 +- test/Integration/Spec.hs | 2 +- test/Rendering/Imports/Spec.hs | 4 ++-- test/Rendering/TOC/Spec.hs | 2 +- test/Semantic/CLI/Spec.hs | 2 +- test/Semantic/IO/Spec.hs | 2 +- test/Semantic/Stat/Spec.hs | 2 +- test/SpecHelpers.hs | 10 ++-------- 12 files changed, 13 insertions(+), 21 deletions(-) diff --git a/semantic.cabal b/semantic.cabal index 662e35303..32ea71937 100644 --- a/semantic.cabal +++ b/semantic.cabal @@ -141,7 +141,6 @@ library , bifunctors , bytestring , cmark-gfm - , comonad , containers , directory , effects @@ -162,7 +161,6 @@ library , parsers , pointed , recursion-schemes - , semigroups , scientific , split , stm-chans diff --git a/test/Assigning/Assignment/Spec.hs b/test/Assigning/Assignment/Spec.hs index ea1969012..e4327a153 100644 --- a/test/Assigning/Assignment/Spec.hs +++ b/test/Assigning/Assignment/Spec.hs @@ -1,5 +1,5 @@ {-# LANGUAGE DataKinds #-} -module Assigning.Assignment.Spec where +module Assigning.Assignment.Spec (spec) where import Assigning.Assignment import Data.AST diff --git a/test/Data/Functor/Classes/Generic/Spec.hs b/test/Data/Functor/Classes/Generic/Spec.hs index e1cca2d59..01d4e41a5 100644 --- a/test/Data/Functor/Classes/Generic/Spec.hs +++ b/test/Data/Functor/Classes/Generic/Spec.hs @@ -1,4 +1,4 @@ -module Data.Functor.Classes.Generic.Spec where +module Data.Functor.Classes.Generic.Spec (spec) where import Data.Functor.Classes.Generic import Data.Functor.Listable diff --git a/test/Data/Mergeable/Spec.hs b/test/Data/Mergeable/Spec.hs index 9f3bd3cfe..92493e060 100644 --- a/test/Data/Mergeable/Spec.hs +++ b/test/Data/Mergeable/Spec.hs @@ -1,5 +1,5 @@ {-# LANGUAGE RankNTypes, ScopedTypeVariables #-} -module Data.Mergeable.Spec where +module Data.Mergeable.Spec (spec) where import Control.Applicative (Alternative(..)) import Data.Functor.Identity diff --git a/test/Data/Source/Spec.hs b/test/Data/Source/Spec.hs index a0da10b93..a48820dd3 100644 --- a/test/Data/Source/Spec.hs +++ b/test/Data/Source/Spec.hs @@ -1,4 +1,4 @@ -module Data.Source.Spec where +module Data.Source.Spec (spec) where import Data.Char (chr) import Data.Functor.Listable diff --git a/test/Integration/Spec.hs b/test/Integration/Spec.hs index 607483abc..b601587f9 100644 --- a/test/Integration/Spec.hs +++ b/test/Integration/Spec.hs @@ -1,5 +1,5 @@ {-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving, OverloadedStrings #-} -module Integration.Spec where +module Integration.Spec (spec) where import qualified Data.ByteString as B import Data.Foldable (find, traverse_) diff --git a/test/Rendering/Imports/Spec.hs b/test/Rendering/Imports/Spec.hs index 77051325f..1feb80f53 100644 --- a/test/Rendering/Imports/Spec.hs +++ b/test/Rendering/Imports/Spec.hs @@ -1,4 +1,4 @@ -module Rendering.Imports.Spec where +module Rendering.Imports.Spec (spec) where import Analysis.Declaration (HasDeclaration, declarationAlgebra) import Analysis.ModuleDef (HasModuleDef, moduleDefAlgebra) @@ -10,7 +10,7 @@ import qualified Data.Map as Map import qualified Semantic.Util as Util import Rendering.Imports import Rendering.Renderer -import Rendering.TOC.Spec +import Rendering.TOC.Spec hiding (spec) import Semantic import Semantic.Task import SpecHelpers diff --git a/test/Rendering/TOC/Spec.hs b/test/Rendering/TOC/Spec.hs index fd23648b9..acc3b60a0 100644 --- a/test/Rendering/TOC/Spec.hs +++ b/test/Rendering/TOC/Spec.hs @@ -1,5 +1,5 @@ {-# LANGUAGE DataKinds, TypeOperators #-} -module Rendering.TOC.Spec where +module Rendering.TOC.Spec (spec) where import Analysis.Decorator (constructorNameAndConstantFields) import Analysis.Declaration diff --git a/test/Semantic/CLI/Spec.hs b/test/Semantic/CLI/Spec.hs index 209797908..d650797a3 100644 --- a/test/Semantic/CLI/Spec.hs +++ b/test/Semantic/CLI/Spec.hs @@ -1,5 +1,5 @@ {-# LANGUAGE DuplicateRecordFields #-} -module Semantic.CLI.Spec where +module Semantic.CLI.Spec (spec) where import Control.Monad (when) import Data.ByteString (ByteString) diff --git a/test/Semantic/IO/Spec.hs b/test/Semantic/IO/Spec.hs index d0ae83566..8bc6d391c 100644 --- a/test/Semantic/IO/Spec.hs +++ b/test/Semantic/IO/Spec.hs @@ -1,4 +1,4 @@ -module Semantic.IO.Spec where +module Semantic.IO.Spec (spec) where import Data.Blob import Data.Functor.Both as Both diff --git a/test/Semantic/Stat/Spec.hs b/test/Semantic/Stat/Spec.hs index 6fd3f2209..9928ad030 100644 --- a/test/Semantic/Stat/Spec.hs +++ b/test/Semantic/Stat/Spec.hs @@ -1,4 +1,4 @@ -module Semantic.Stat.Spec where +module Semantic.Stat.Spec (spec) where import Semantic.Stat import Test.Hspec hiding (shouldBe, shouldNotBe, shouldThrow, errorCall) diff --git a/test/SpecHelpers.hs b/test/SpecHelpers.hs index 0cfb9c9f2..2df78cfdb 100644 --- a/test/SpecHelpers.hs +++ b/test/SpecHelpers.hs @@ -3,7 +3,6 @@ module SpecHelpers ( diffFilePaths , parseFilePath , readFilePair -, languageForFilePath , Verbatim(..) , verbatim , readFileVerbatim @@ -31,18 +30,13 @@ diffFilePaths paths = readFilePair paths >>= runTask . diffBlobPair SExpressionD -- | Returns an s-expression parse tree for the specified FilePath. parseFilePath :: FilePath -> IO B.ByteString -parseFilePath path = IO.readFile path (languageForFilePath path) >>= pure . fromJust >>= runTask . parseBlob SExpressionTermRenderer +parseFilePath path = IO.readFile path (IO.languageForFilePath path) >>= pure . fromJust >>= runTask . parseBlob SExpressionTermRenderer -- | Read two files to a BlobPair. readFilePair :: Both FilePath -> IO BlobPair -readFilePair paths = let paths' = fmap (\p -> (p, languageForFilePath p)) paths in +readFilePair paths = let paths' = fmap (\p -> (p, IO.languageForFilePath p)) paths in runBothWith IO.readFilePair paths' --- | Returns a Maybe Language based on the FilePath's extension. -languageForFilePath :: FilePath -> Maybe Language -languageForFilePath = languageForType . takeExtension - - readFileVerbatim :: FilePath -> IO Verbatim readFileVerbatim = fmap verbatim . B.readFile From 6d5561f9b9d7805192f7b55d3befdff924dc11e7 Mon Sep 17 00:00:00 2001 From: Patrick Thomson Date: Mon, 12 Mar 2018 10:51:07 -0400 Subject: [PATCH 13/16] fix misalignment --- bench/Main.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/bench/Main.hs b/bench/Main.hs index cf6e76147..94400e61a 100644 --- a/bench/Main.hs +++ b/bench/Main.hs @@ -19,9 +19,9 @@ rbEval = whnfIO . fmap show . evaluateRubyFile . ("bench/bench-fixtures/ruby/" < main :: IO () main = defaultMain [ bgroup "python" [ bench "assignment" $ pyEval "simple-assignment.py" - , bench "function def" $ pyEval "function-definition.py" - , bench "if + function calls" $ pyEval "if-statement-functions.py" - ] + , bench "function def" $ pyEval "function-definition.py" + , bench "if + function calls" $ pyEval "if-statement-functions.py" + ] , bgroup "ruby" [ bench "assignment" $ rbEval "simple-assignment.rb" , bench "function def" $ rbEval "function-definition.rb" , bench "if + function calls" $ rbEval "if-statement-functions.rb" From 8334619f952b30bd89e7c586356d4256afe6a97f Mon Sep 17 00:00:00 2001 From: Patrick Thomson Date: Mon, 12 Mar 2018 11:15:21 -0400 Subject: [PATCH 14/16] DRY --- src/Semantic/Util.hs | 10 ++++++---- 1 file changed, 6 insertions(+), 4 deletions(-) diff --git a/src/Semantic/Util.hs b/src/Semantic/Util.hs index f8de52424..106ec6377 100644 --- a/src/Semantic/Util.hs +++ b/src/Semantic/Util.hs @@ -29,10 +29,12 @@ import qualified Language.Ruby.Assignment as Ruby import qualified Language.Python.Assignment as Python import qualified Language.TypeScript.Assignment as TypeScript -type GoValue = Value Precise (Term (Union Go.Syntax) (Record Location)) -type RubyValue = Value Precise (Term (Union Ruby.Syntax) (Record Location)) -type PythonValue = Value Precise (Term (Union Python.Syntax) (Record Location)) -type TypeScriptValue = Value Precise (Term (Union TypeScript.Syntax) (Record Location)) +type Language a = Value Precise (Term (Union a) (Record Location)) + +type GoValue = Language Go.Syntax +type RubyValue = Language Ruby.Syntax +type PythonValue = Language Python.Syntax +type TypeScriptValue = Language TypeScript.Syntax file :: MonadIO m => FilePath -> m Blob file path = fromJust <$> IO.readFile path (languageForFilePath path) From 8bebe26ea9af6ff0b4095e39499c7b2ef2785189 Mon Sep 17 00:00:00 2001 From: Patrick Thomson Date: Mon, 12 Mar 2018 11:18:14 -0400 Subject: [PATCH 15/16] use the canonical definition of interface --- src/Data/Syntax/Declaration.hs | 2 -- 1 file changed, 2 deletions(-) diff --git a/src/Data/Syntax/Declaration.hs b/src/Data/Syntax/Declaration.hs index cc29a427d..8ed52684d 100644 --- a/src/Data/Syntax/Declaration.hs +++ b/src/Data/Syntax/Declaration.hs @@ -163,8 +163,6 @@ instance Show1 Module where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Module where eval (Module _ xs) = eval' xs where - interface val = pure val -- inj . Value.Interface val <$> askLocalEnv - eval' [] = unit >>= interface eval' [x] = subtermValue x >>= interface eval' (x:xs) = do From 668fc45e639e367014da75e14116ed126478852a Mon Sep 17 00:00:00 2001 From: Patrick Thomson Date: Mon, 12 Mar 2018 11:23:14 -0400 Subject: [PATCH 16/16] add evaluateGoFile --- src/Semantic/Util.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Semantic/Util.hs b/src/Semantic/Util.hs index 106ec6377..f1e534805 100644 --- a/src/Semantic/Util.hs +++ b/src/Semantic/Util.hs @@ -52,6 +52,9 @@ evaluateRubyFiles paths = do typecheckGoFile path = evaluateCache @Type <$> (file path >>= runTask . parse goParser) +evaluateGoFile path = evaluateCache @GoValue <$> + (file path >>= runTask . parse goParser) + -- Python typecheckPythonFile path = evaluateCache @Type <$> (file path >>= runTask . parse pythonParser)