Skip to content
This repository was archived by the owner on Apr 1, 2025. It is now read-only.
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 1 addition & 1 deletion .hlint.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -67,7 +67,7 @@
# Conveniences
- warning: {lhs: maybe a pure, rhs: maybeM a, name: Use maybeM}
- warning: {lhs: either (const a) id, rhs: fromRight a, name: use fromRight}
- warning: {lhs: either id (const a), rhs: fromLeft a, name: use fromRight}
- warning: {lhs: either id (const a), rhs: fromLeft a, name: use fromLeft}

# Applicative style
- warning: {lhs: f <$> pure a <*> b, rhs: f a <$> b, name: Avoid redundant pure}
Expand Down
2 changes: 1 addition & 1 deletion semantic-core/src/Analysis/Concrete.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE FlexibleContexts, FlexibleInstances, GeneralizedNewtypeDeriving, LambdaCase, MultiParamTypeClasses, NamedFieldPuns, RecordWildCards, TypeApplications, TypeOperators, UndecidableInstances #-}
{-# LANGUAGE FlexibleContexts, FlexibleInstances, LambdaCase, MultiParamTypeClasses, NamedFieldPuns, RecordWildCards, TypeOperators, UndecidableInstances #-}
module Analysis.Concrete
( Concrete(..)
, concrete
Expand Down
2 changes: 1 addition & 1 deletion semantic-core/src/Analysis/Eval.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE FlexibleContexts, GeneralizedNewtypeDeriving, LambdaCase, RankNTypes, RecordWildCards #-}
{-# LANGUAGE FlexibleContexts, LambdaCase, RankNTypes, RecordWildCards #-}
module Analysis.Eval
( eval
, prog1
Expand Down
2 changes: 1 addition & 1 deletion semantic-core/src/Analysis/Typecheck.hs
Original file line number Diff line number Diff line change
Expand Up @@ -160,7 +160,7 @@ typecheckingAnalysis = Analysis{..}
bool _ = pure MBool
asBool b = unify MBool b >> pure True <|> pure False
string _ = pure MString
asString s = unify MString s *> pure ""
asString s = unify MString s $> ""
frame = fail "unimplemented"
edge _ _ = pure ()
_ ... m = m
Expand Down
2 changes: 1 addition & 1 deletion semantic-core/src/Control/Effect/Readline.hs
Original file line number Diff line number Diff line change
Expand Up @@ -81,7 +81,7 @@ instance (Carrier sig m, Effect sig, MonadException m, MonadIO m) => Carrier (Re

runReadlineWithHistory :: MonadException m => ReadlineC m a -> m a
runReadlineWithHistory block = do
homeDir <- liftIO $ getHomeDirectory
homeDir <- liftIO getHomeDirectory
prefs <- liftIO $ readPrefs (homeDir </> ".haskeline")
let settingsDir = homeDir </> ".local/semantic-core"
settings = Settings
Expand Down
2 changes: 1 addition & 1 deletion semantic-core/test/Spec.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE OverloadedStrings, TypeApplications #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}

module Main (main) where
Expand Down
2 changes: 1 addition & 1 deletion src/Data/Language.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, KindSignatures, LambdaCase #-}
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, KindSignatures #-}
module Data.Language
( Language (..)
, SLanguage (..)
Expand Down
2 changes: 1 addition & 1 deletion src/Data/Project.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, KindSignatures, MultiWayIf #-}
{-# LANGUAGE DeriveAnyClass, MultiWayIf #-}

module Data.Project
( Project (..)
Expand Down
4 changes: 2 additions & 2 deletions src/Semantic/Git.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,7 @@ import Control.Monad.IO.Class
import Data.Attoparsec.Text (Parser)
import Data.Attoparsec.Text as AP
import Data.Char
import Data.Either (fromRight)
import Data.Text as Text
import Shelly hiding (FilePath)
import System.IO (hSetBinaryMode)
Expand All @@ -42,7 +43,7 @@ sh = shelly . silently . onCommandHandles (initOutputHandles (`hSetBinaryMode` T

-- | Parses an list of entries separated by \NUL, and on failure return []
parseEntries :: Text -> [TreeEntry]
parseEntries = either (const []) id . AP.parseOnly everything
parseEntries = fromRight [] . AP.parseOnly everything
where
everything = AP.sepBy entryParser "\NUL" <* "\NUL\n" <* AP.endOfInput

Expand Down Expand Up @@ -87,4 +88,3 @@ data TreeEntry
, treeEntryOid :: OID
, treeEntryPath :: FilePath
} deriving (Eq, Show)

2 changes: 1 addition & 1 deletion src/Tags/Taggable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -189,7 +189,7 @@ instance Taggable Expression.Call where
instance Taggable Ruby.Send where
snippet ann (Ruby.Send _ _ _ (Just (Term (In body _)))) = Just $ subtractLocation ann body
snippet ann _ = Just $ locationByteRange ann
symbolName Ruby.Send{..} = maybe Nothing declaredName sendSelector
symbolName Ruby.Send{..} = declaredName =<< sendSelector

instance Taggable []
instance Taggable Comment.Comment
Expand Down
14 changes: 7 additions & 7 deletions test/Analysis/Go/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ module Analysis.Go.Spec (spec) where

import qualified Data.Abstract.ModuleTable as ModuleTable
import qualified Data.Language as Language
import SpecHelpers
import SpecHelpers


spec :: (?session :: TaskSession) => Spec
Expand All @@ -14,19 +14,19 @@ spec = parallel $ do
(scopeGraph, (heap, res)) <- evaluate ["main.go", "foo/foo.go", "bar/bar.go", "bar/rab.go"]
case ModuleTable.lookup "main.go" <$> res of
Right (Just (Module _ (scopeAndFrame, _))) -> do
() <$ SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldBe` Just ()
SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
SpecHelpers.lookupMembers "foo" Import scopeAndFrame heap scopeGraph `shouldBe` Just ["New"]
() <$ SpecHelpers.lookupDeclaration "main" scopeAndFrame heap scopeGraph `shouldBe` Just ()
() <$ SpecHelpers.lookupDeclaration "Bar" scopeAndFrame heap scopeGraph `shouldBe` Just ()
() <$ SpecHelpers.lookupDeclaration "Rab" scopeAndFrame heap scopeGraph `shouldBe` Just ()
SpecHelpers.lookupDeclaration "main" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
SpecHelpers.lookupDeclaration "Bar" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
SpecHelpers.lookupDeclaration "Rab" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
other -> expectationFailure (show other)

it "imports with aliases (and side effects only)" $ do
(scopeGraph, (heap, res)) <- evaluate ["main1.go", "foo/foo.go", "bar/bar.go", "bar/rab.go"]
case ModuleTable.lookup "main1.go" <$> res of
Right (Just (Module _ (scopeAndFrame, _))) -> do
const () <$> SpecHelpers.lookupDeclaration "f" scopeAndFrame heap scopeGraph `shouldBe` Just ()
const () <$> SpecHelpers.lookupDeclaration "main" scopeAndFrame heap scopeGraph `shouldBe` Just ()
SpecHelpers.lookupDeclaration "f" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
SpecHelpers.lookupDeclaration "main" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
-- (lookupDeclaration "f" heap >>= deNamespace heap) `shouldBe` Just ("f", ["New"])
other -> expectationFailure (show other)

Expand Down
12 changes: 6 additions & 6 deletions test/Analysis/PHP/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,25 +16,25 @@ spec = parallel $ do
case ModuleTable.lookup "main.php" <$> res of
Right (Just (Module _ (scopeAndFrame, value))) -> do
value `shouldBe` Value.Unit
const () <$> SpecHelpers.lookupDeclaration "bar" scopeAndFrame heap scopeGraph `shouldBe` Just ()
const () <$> SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldBe` Just ()
SpecHelpers.lookupDeclaration "bar" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
other -> expectationFailure (show other)

xit "evaluates include_once and require_once" $ do
(scopeGraph, (heap, res)) <- evaluate ["main_once.php", "foo.php", "bar.php"]
case ModuleTable.lookup "main_once.php" <$> res of
Right (Just (Module _ (scopeAndFrame, value))) -> do
value `shouldBe` Value.Unit
const () <$> SpecHelpers.lookupDeclaration "bar" scopeAndFrame heap scopeGraph `shouldBe` Just ()
const () <$> SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldBe` Just ()
SpecHelpers.lookupDeclaration "bar" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
other -> expectationFailure (show other)

xit "evaluates namespaces" $ do
(scopeGraph, (heap, res)) <- evaluate ["namespaces.php"]
case ModuleTable.lookup "namespaces.php" <$> res of
Right (Just (Module _ (scopeAndFrame, _))) -> do
const () <$> SpecHelpers.lookupDeclaration "Foo" scopeAndFrame heap scopeGraph `shouldBe` Just ()
const () <$> SpecHelpers.lookupDeclaration "NS1" scopeAndFrame heap scopeGraph `shouldBe` Just ()
SpecHelpers.lookupDeclaration "Foo" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
SpecHelpers.lookupDeclaration "NS1" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust

undefined
-- (derefQName heap ("NS1" :| []) env >>= deNamespace heap) `shouldBe` Just ("NS1", ["Sub1", "b", "c"])
Expand Down
18 changes: 9 additions & 9 deletions test/Analysis/Python/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,8 +16,8 @@ spec = parallel $ do
(scopeGraph, (heap, res)) <- evaluate ["main.py", "a.py", "b/__init__.py", "b/c.py"]
case ModuleTable.lookup "main.py" <$> res of
Right (Just (Module _ (scopeAndFrame, _))) -> do
const () <$> SpecHelpers.lookupDeclaration "a" scopeAndFrame heap scopeGraph `shouldBe` Just ()
const () <$> SpecHelpers.lookupDeclaration "b" scopeAndFrame heap scopeGraph `shouldBe` Just ()
SpecHelpers.lookupDeclaration "a" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
SpecHelpers.lookupDeclaration "b" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust

fromJust (SpecHelpers.lookupMembers "a" Import scopeAndFrame heap scopeGraph) `shouldContain` [ "foo" ]
fromJust (SpecHelpers.lookupMembers "b" Import scopeAndFrame heap scopeGraph) `shouldContain` ["c"]
Expand All @@ -28,16 +28,16 @@ spec = parallel $ do
(scopeGraph, (heap, res)) <- evaluate ["main1.py", "a.py", "b/__init__.py", "b/c.py"]
case ModuleTable.lookup "main1.py" <$> res of
Right (Just (Module _ (scopeAndFrame, _))) -> do
const () <$> SpecHelpers.lookupDeclaration "b" scopeAndFrame heap scopeGraph `shouldBe` Just ()
const () <$> SpecHelpers.lookupDeclaration "e" scopeAndFrame heap scopeGraph `shouldBe` Just ()
SpecHelpers.lookupDeclaration "b" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
SpecHelpers.lookupDeclaration "e" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
other -> expectationFailure (show other)

it "imports using from syntax" $ do
(scopeGraph, (heap, res)) <- evaluate ["main2.py", "a.py", "b/__init__.py", "b/c.py"]
case ModuleTable.lookup "main2.py" <$> res of
Right (Just (Module _ (scopeAndFrame, _))) -> do
const () <$> SpecHelpers.lookupDeclaration "bar" scopeAndFrame heap scopeGraph `shouldBe` Just ()
const () <$> SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldBe` Just ()
SpecHelpers.lookupDeclaration "bar" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust

-- TODO: Enable when we constrain edge paths with path predicates
-- () <$ SpecHelpers.lookupDeclaration "baz" heap scopeGraph `shouldBe` Nothing
Expand All @@ -47,16 +47,16 @@ spec = parallel $ do
(scopeGraph, (heap, res)) <- evaluate ["main3.py", "c/__init__.py", "c/utils.py"]
case ModuleTable.lookup "main3.py" <$> res of
Right (Just (Module _ (scopeAndFrame, _))) -> do
const () <$> SpecHelpers.lookupDeclaration "utils" scopeAndFrame heap scopeGraph `shouldBe` Just ()
SpecHelpers.lookupDeclaration "utils" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
-- (lookupDeclaration "utils" heap >>= deNamespace heap) `shouldBe` Just ("utils", ["to_s"])
other -> expectationFailure (show other)

it "subclasses" $ do
(scopeGraph, (heap, res)) <- evaluate ["subclass.py"]
case ModuleTable.lookup "subclass.py" <$> res of
Right (Just (Module _ (scopeAndFrame, value))) -> do
() <$ SpecHelpers.lookupDeclaration "Foo" scopeAndFrame heap scopeGraph `shouldBe` Just ()
() <$ SpecHelpers.lookupDeclaration "Bar" scopeAndFrame heap scopeGraph `shouldBe` Just ()
SpecHelpers.lookupDeclaration "Foo" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
SpecHelpers.lookupDeclaration "Bar" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
SpecHelpers.lookupMembers "Bar" Superclass scopeAndFrame heap scopeGraph `shouldBe` Just [ "dang" ]
value `shouldBe` String "\"bar\""
other -> expectationFailure (show other)
Expand Down
14 changes: 7 additions & 7 deletions test/Analysis/Ruby/Spec.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
{-# OPTIONS_GHC -O0 #-}
{-# LANGUAGE ImplicitParams, TupleSections #-}
{-# LANGUAGE ImplicitParams #-}
module Analysis.Ruby.Spec (spec) where

import Control.Abstract (Declaration (..), ScopeError (..))
Expand All @@ -22,15 +22,15 @@ spec = parallel $ do
case ModuleTable.lookup "main.rb" <$> res of
Right (Just (Module _ (scopeAndFrame, value))) -> do
value `shouldBe` Value.Integer (Number.Integer 1)
() <$ SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldBe` Just ()
SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
other -> expectationFailure (show other)

it "evaluates load" $ do
(scopeGraph, (heap, res)) <- evaluate ["load.rb", "foo.rb"]
case ModuleTable.lookup "load.rb" <$> res of
Right (Just (Module _ (scopeAndFrame, value))) -> do
value `shouldBe` Value.Integer (Number.Integer 1)
() <$ SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldBe` Just ()
SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
other -> expectationFailure (show other)

it "evaluates load with wrapper" $ do
Expand All @@ -42,16 +42,16 @@ spec = parallel $ do
case ModuleTable.lookup "subclass.rb" <$> res of
Right (Just (Module _ (scopeAndFrame, value))) -> do
value `shouldBe` String "\"<bar>\""
() <$ SpecHelpers.lookupDeclaration "Bar" scopeAndFrame heap scopeGraph `shouldBe` Just ()
() <$ SpecHelpers.lookupDeclaration "Foo" scopeAndFrame heap scopeGraph `shouldBe` Just ()
SpecHelpers.lookupDeclaration "Bar" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
SpecHelpers.lookupDeclaration "Foo" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
SpecHelpers.lookupMembers "Bar" Superclass scopeAndFrame heap scopeGraph `shouldBe` Just ["baz", "foo", "inspect"]
other -> expectationFailure (show other)

it "evaluates modules" $ do
(scopeGraph, (heap, res)) <- evaluate ["modules.rb"]
case ModuleTable.lookup "modules.rb" <$> res of
Right (Just (Module _ (scopeAndFrame, _))) -> do
const () <$> SpecHelpers.lookupDeclaration "Bar" scopeAndFrame heap scopeGraph `shouldBe` Just ()
SpecHelpers.lookupDeclaration "Bar" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
other -> expectationFailure (show other)

it "handles break correctly" $ do
Expand Down Expand Up @@ -95,7 +95,7 @@ spec = parallel $ do
case ModuleTable.lookup "puts.rb" <$> res of
Right (Just (Module _ (scopeAndFrame, value))) -> do
value `shouldBe` Unit
const () <$> SpecHelpers.lookupDeclaration "puts" scopeAndFrame heap scopeGraph `shouldBe` Just ()
SpecHelpers.lookupDeclaration "puts" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
other -> expectationFailure (show other)

where
Expand Down
24 changes: 12 additions & 12 deletions test/Analysis/TypeScript/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,53 +29,53 @@ spec = parallel $ do
(scopeGraph, (heap, res)) <- evaluate ["main6.ts", "baz.ts", "foo.ts"]
case ModuleTable.lookup "main6.ts" <$> res of
Right (Just (Module _ (scopeAndFrame, _))) -> do
() <$ SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldBe` Just ()
SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
other -> expectationFailure (show other)

it "imports with aliased symbols" $ do
(scopeGraph, (heap, res)) <- evaluate ["main.ts", "foo.ts", "foo/b.ts"]
case ModuleTable.lookup "main.ts" <$> res of
Right (Just (Module _ (scopeAndFrame, _))) -> do
const () <$> SpecHelpers.lookupDeclaration "bar" scopeAndFrame heap scopeGraph `shouldBe` Just ()
const () <$> SpecHelpers.lookupDeclaration "quz" scopeAndFrame heap scopeGraph `shouldBe` Just ()
SpecHelpers.lookupDeclaration "bar" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
SpecHelpers.lookupDeclaration "quz" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust

other -> expectationFailure (show other)

it "imports with qualified names" $ do
(scopeGraph, (heap, res)) <- evaluate ["main1.ts", "foo.ts", "a.ts"]
case ModuleTable.lookup "main1.ts" <$> res of
Right (Just (Module _ (scopeAndFrame, _))) -> do
() <$ SpecHelpers.lookupDeclaration "b" scopeAndFrame heap scopeGraph `shouldBe` Just ()
() <$ SpecHelpers.lookupDeclaration "z" scopeAndFrame heap scopeGraph `shouldBe` Just ()
SpecHelpers.lookupDeclaration "b" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
SpecHelpers.lookupDeclaration "z" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust

lookupMembers "b" Import scopeAndFrame heap scopeGraph `shouldBe` Just [ "baz", "foo" ]
lookupMembers "z" Import scopeAndFrame heap scopeGraph `shouldBe` Just [ "baz", "foo" ]

() <$ SpecHelpers.lookupDeclaration "baz" scopeAndFrame heap scopeGraph `shouldBe` Nothing
() <$ SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldBe` Nothing
SpecHelpers.lookupDeclaration "baz" scopeAndFrame heap scopeGraph `shouldBe` Nothing
SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldBe` Nothing
other -> expectationFailure (show other)

it "stores function declaration in scope graph" $ do
(scopeGraph, (heap, res)) <- evaluate ["a.ts"]
case ModuleTable.lookup "a.ts" <$> res of
Right (Just (Module _ (scopeAndFrame, value))) -> do
const () <$> SpecHelpers.lookupDeclaration "baz" scopeAndFrame heap scopeGraph `shouldBe` Just ()
SpecHelpers.lookupDeclaration "baz" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
value `shouldBe` Unit
other -> expectationFailure (show other)

it "imports functions" $ do
(scopeGraph, (heap, res)) <- evaluate ["main4.ts", "foo.ts"]
case ModuleTable.lookup "main4.ts" <$> res of
Right (Just (Module _ (scopeAndFrame, value))) -> do
const () <$> SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldBe` Just ()
SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
value `shouldBe` String (pack "\"this is the foo function\"")
other -> expectationFailure (show other)

it "side effect only imports dont expose exports" $ do
(scopeGraph, (heap, res)) <- evaluate ["main3.ts", "a.ts"]
case ModuleTable.lookup "main3.ts" <$> res of
Right (Just (Module _ (scopeAndFrame, value))) -> do
() <$ SpecHelpers.lookupDeclaration "baz" scopeAndFrame heap scopeGraph `shouldBe` Nothing
SpecHelpers.lookupDeclaration "baz" scopeAndFrame heap scopeGraph `shouldBe` Nothing
value `shouldBe` Unit
Heap.heapSize heap `shouldBe` 4
other -> expectationFailure (show other)
Expand All @@ -88,7 +88,7 @@ spec = parallel $ do
(scopeGraph, (heap, res)) <- evaluate ["early-return.ts"]
case ModuleTable.lookup "early-return.ts" <$> res of
Right (Just (Module _ (scopeAndFrame, _))) ->
const () <$> SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldBe` Just ()
SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
other -> expectationFailure (show other)

it "evaluates sequence expressions" $ do
Expand Down Expand Up @@ -117,7 +117,7 @@ spec = parallel $ do
case ModuleTable.lookup "await.ts" <$> res of
Right (Just (Module _ (scopeAndFrame, _))) -> do
-- Test that f2 is in the scopegraph and heap.
const () <$> SpecHelpers.lookupDeclaration "f2" scopeAndFrame heap scopeGraph `shouldBe` Just ()
SpecHelpers.lookupDeclaration "f2" scopeAndFrame heap scopeGraph `shouldSatisfy` isJust
-- Test we can't reference y from outside the function
SpecHelpers.lookupDeclaration "y" scopeAndFrame heap scopeGraph `shouldBe` Nothing
other -> expectationFailure (show other)
Expand Down
Loading