mirror of
https://github.com/github/semantic.git
synced 2024-11-28 01:47:01 +03:00
Merge remote-tracking branch 'origin/master' into eval-__FILE__
This commit is contained in:
commit
a5cc587b85
@ -20,6 +20,7 @@ import Control.Monad.Effect.State as X
|
|||||||
import Control.Monad.Effect.Resumable as X
|
import Control.Monad.Effect.Resumable as X
|
||||||
import Data.Abstract.Module
|
import Data.Abstract.Module
|
||||||
import Data.Coerce
|
import Data.Coerce
|
||||||
|
import Data.Empty as Empty
|
||||||
import Data.Type.Coercion
|
import Data.Type.Coercion
|
||||||
import Prologue
|
import Prologue
|
||||||
|
|
||||||
@ -37,7 +38,7 @@ class MonadEvaluator location term value effects m => MonadAnalysis location ter
|
|||||||
|
|
||||||
-- | Isolate the given action with an empty global environment and exports.
|
-- | Isolate the given action with an empty global environment and exports.
|
||||||
isolate :: m effects a -> m effects a
|
isolate :: m effects a -> m effects a
|
||||||
isolate = withEnv mempty . withExports mempty
|
isolate = withEnv Empty.empty . withExports Empty.empty
|
||||||
|
|
||||||
|
|
||||||
-- | Lift a 'SubtermAlgebra' for an underlying analysis into a containing analysis. Use this when defining an analysis which can be composed onto other analyses to ensure that a call to 'analyzeTerm' occurs in the inner analysis and not the outer one.
|
-- | Lift a 'SubtermAlgebra' for an underlying analysis into a containing analysis. Use this when defining an analysis which can be composed onto other analyses to ensure that a call to 'analyzeTerm' occurs in the inner analysis and not the outer one.
|
||||||
|
@ -63,7 +63,7 @@ import Data.Abstract.Module
|
|||||||
import Data.Abstract.ModuleTable
|
import Data.Abstract.ModuleTable
|
||||||
import Data.Abstract.Package
|
import Data.Abstract.Package
|
||||||
import Data.Abstract.Origin
|
import Data.Abstract.Origin
|
||||||
import Data.Empty
|
import Data.Empty as Empty
|
||||||
import qualified Data.IntMap as IntMap
|
import qualified Data.IntMap as IntMap
|
||||||
import Data.Semigroup.Reducer
|
import Data.Semigroup.Reducer
|
||||||
import Lens.Micro
|
import Lens.Micro
|
||||||
@ -106,10 +106,10 @@ deriving instance (Ord (Cell location value), Ord location, Ord term, Ord value,
|
|||||||
deriving instance (Show (Cell location value), Show location, Show term, Show value, Show (Base term ())) => Show (EvaluatorState location term value)
|
deriving instance (Show (Cell location value), Show location, Show term, Show value, Show (Base term ())) => Show (EvaluatorState location term value)
|
||||||
|
|
||||||
instance (Ord location, Semigroup (Cell location value)) => Semigroup (EvaluatorState location term value) where
|
instance (Ord location, Semigroup (Cell location value)) => Semigroup (EvaluatorState location term value) where
|
||||||
EvaluatorState e1 h1 m1 l1 x1 j1 o1 <> EvaluatorState e2 h2 m2 l2 x2 j2 o2 = EvaluatorState (e1 <> e2) (h1 <> h2) (m1 <> m2) (l1 <> l2) (x1 <> x2) (j1 <> j2) (o1 <> o2)
|
EvaluatorState e1 h1 m1 l1 x1 j1 o1 <> EvaluatorState e2 h2 m2 l2 x2 j2 o2 = EvaluatorState (mergeEnvs e1 e2) (h1 <> h2) (m1 <> m2) (l1 <> l2) (x1 <> x2) (j1 <> j2) (o1 <> o2)
|
||||||
|
|
||||||
instance (Ord location, Semigroup (Cell location value)) => Empty (EvaluatorState location term value) where
|
instance (Ord location, Semigroup (Cell location value)) => Empty (EvaluatorState location term value) where
|
||||||
empty = EvaluatorState mempty mempty mempty mempty mempty mempty mempty
|
empty = EvaluatorState Empty.empty mempty mempty mempty mempty mempty mempty
|
||||||
|
|
||||||
|
|
||||||
-- Lenses
|
-- Lenses
|
||||||
@ -183,7 +183,7 @@ withDefaultEnvironment e = raise . local (const e) . lower
|
|||||||
-- | Obtain an environment that is the composition of the current and default environments.
|
-- | Obtain an environment that is the composition of the current and default environments.
|
||||||
-- Useful for debugging.
|
-- Useful for debugging.
|
||||||
fullEnvironment :: MonadEvaluator location term value effects m => m effects (Environment location value)
|
fullEnvironment :: MonadEvaluator location term value effects m => m effects (Environment location value)
|
||||||
fullEnvironment = mappend <$> getEnv <*> defaultEnvironment
|
fullEnvironment = mergeEnvs <$> getEnv <*> defaultEnvironment
|
||||||
|
|
||||||
-- | Run an action with a locally-modified environment.
|
-- | Run an action with a locally-modified environment.
|
||||||
localEnv :: MonadEvaluator location term value effects m => (Environment location value -> Environment location value) -> m effects a -> m effects a
|
localEnv :: MonadEvaluator location term value effects m => (Environment location value -> Environment location value) -> m effects a -> m effects a
|
||||||
|
@ -17,6 +17,7 @@ import Data.Abstract.Environment as Env
|
|||||||
import Data.Abstract.FreeVariables
|
import Data.Abstract.FreeVariables
|
||||||
import Data.Abstract.Live (Live)
|
import Data.Abstract.Live (Live)
|
||||||
import Data.Abstract.Number as Number
|
import Data.Abstract.Number as Number
|
||||||
|
import Data.Empty as Empty
|
||||||
import Data.Scientific (Scientific)
|
import Data.Scientific (Scientific)
|
||||||
import Data.Semigroup.Reducer hiding (unit)
|
import Data.Semigroup.Reducer hiding (unit)
|
||||||
import Prelude
|
import Prelude
|
||||||
@ -177,10 +178,10 @@ makeNamespace :: ( MonadValue location value effects m
|
|||||||
)
|
)
|
||||||
=> Name
|
=> Name
|
||||||
-> Address location value
|
-> Address location value
|
||||||
-> [value]
|
-> Maybe value
|
||||||
-> m effects value
|
-> m effects value
|
||||||
makeNamespace name addr supers = do
|
makeNamespace name addr super = do
|
||||||
superEnv <- mconcat <$> traverse scopedEnvironment supers
|
superEnv <- maybe (pure Empty.empty) scopedEnvironment super
|
||||||
namespaceEnv <- Env.head <$> getEnv
|
namespaceEnv <- Env.head <$> getEnv
|
||||||
v <- namespace name (Env.mergeNewer superEnv namespaceEnv)
|
v <- namespace name (Env.mergeNewer superEnv namespaceEnv)
|
||||||
v <$ assign addr v
|
v <$ assign addr v
|
||||||
|
@ -5,12 +5,15 @@ module Data.Abstract.Environment
|
|||||||
, bind
|
, bind
|
||||||
, delete
|
, delete
|
||||||
, head
|
, head
|
||||||
|
, emptyEnv
|
||||||
|
, mergeEnvs
|
||||||
, mergeNewer
|
, mergeNewer
|
||||||
, insert
|
, insert
|
||||||
, lookup
|
, lookup
|
||||||
, names
|
, names
|
||||||
, overwrite
|
, overwrite
|
||||||
, pairs
|
, pairs
|
||||||
|
, unpairs
|
||||||
, pop
|
, pop
|
||||||
, push
|
, push
|
||||||
, roots
|
, roots
|
||||||
@ -21,14 +24,14 @@ import Data.Abstract.Address
|
|||||||
import Data.Abstract.FreeVariables
|
import Data.Abstract.FreeVariables
|
||||||
import Data.Abstract.Live
|
import Data.Abstract.Live
|
||||||
import Data.Align
|
import Data.Align
|
||||||
|
import Data.Empty as Empty
|
||||||
import qualified Data.Map as Map
|
import qualified Data.Map as Map
|
||||||
import Data.Semigroup.Reducer
|
|
||||||
import GHC.Exts (IsList (..))
|
import GHC.Exts (IsList (..))
|
||||||
import Prologue
|
import Prologue
|
||||||
import qualified Data.List.NonEmpty as NonEmpty
|
import qualified Data.List.NonEmpty as NonEmpty
|
||||||
|
|
||||||
-- $setup
|
-- $setup
|
||||||
-- >>> let bright = push (insert (name "foo") (Address (Precise 0)) mempty)
|
-- >>> let bright = push (insert (name "foo") (Address (Precise 0)) emptyEnv)
|
||||||
-- >>> let shadowed = insert (name "foo") (Address (Precise 1)) bright
|
-- >>> let shadowed = insert (name "foo") (Address (Precise 1)) bright
|
||||||
|
|
||||||
-- | A LIFO stack of maps of names to addresses, representing a lexically-scoped evaluation environment.
|
-- | A LIFO stack of maps of names to addresses, representing a lexically-scoped evaluation environment.
|
||||||
@ -49,18 +52,15 @@ instance IsList (Environment l a) where
|
|||||||
fromList xs = Environment (Map.fromList xs :| [])
|
fromList xs = Environment (Map.fromList xs :| [])
|
||||||
toList (Environment (x :| _)) = Map.toList x
|
toList (Environment (x :| _)) = Map.toList x
|
||||||
|
|
||||||
-- TODO: property-check me
|
instance Empty (Environment l a) where
|
||||||
instance Semigroup (Environment l a) where
|
empty = emptyEnv
|
||||||
Environment (a :| as) <> Environment (b :| bs) =
|
|
||||||
Environment ((a <> b) :| alignWith (mergeThese (<>)) as bs)
|
|
||||||
|
|
||||||
instance Reducer (Name, Address l a) (Environment l a) where
|
mergeEnvs :: Environment l a -> Environment l a -> Environment l a
|
||||||
unit a = Environment (unit a :| [])
|
mergeEnvs (Environment (a :| as)) (Environment (b :| bs)) =
|
||||||
|
Environment ((<>) a b :| alignWith (mergeThese (<>)) as bs)
|
||||||
|
|
||||||
-- | This instance is possibly unlawful. If this breaks, you get to keep both pieces.
|
emptyEnv :: Environment l a
|
||||||
instance Monoid (Environment l a) where
|
emptyEnv = Environment (Empty.empty :| [])
|
||||||
mappend = (<>)
|
|
||||||
mempty = Environment (mempty :| [])
|
|
||||||
|
|
||||||
-- | Make and enter a new empty scope in the given environment.
|
-- | Make and enter a new empty scope in the given environment.
|
||||||
push :: Environment l a -> Environment l a
|
push :: Environment l a -> Environment l a
|
||||||
@ -68,7 +68,7 @@ push (Environment (a :| as)) = Environment (mempty :| a : as)
|
|||||||
|
|
||||||
-- | Remove the frontmost scope.
|
-- | Remove the frontmost scope.
|
||||||
pop :: Environment l a -> Environment l a
|
pop :: Environment l a -> Environment l a
|
||||||
pop (Environment (_ :| [])) = mempty
|
pop (Environment (_ :| [])) = Empty.empty
|
||||||
pop (Environment (_ :| a : as)) = Environment (a :| as)
|
pop (Environment (_ :| a : as)) = Environment (a :| as)
|
||||||
|
|
||||||
-- | Drop all scopes save for the frontmost one.
|
-- | Drop all scopes save for the frontmost one.
|
||||||
@ -92,6 +92,9 @@ mergeNewer (Environment a) (Environment b) =
|
|||||||
pairs :: Environment l a -> [(Name, Address l a)]
|
pairs :: Environment l a -> [(Name, Address l a)]
|
||||||
pairs = Map.toList . fold . unEnvironment
|
pairs = Map.toList . fold . unEnvironment
|
||||||
|
|
||||||
|
unpairs :: [(Name, Address l a)] -> Environment l a
|
||||||
|
unpairs = fromList
|
||||||
|
|
||||||
-- | Lookup a 'Name' in the environment.
|
-- | Lookup a 'Name' in the environment.
|
||||||
--
|
--
|
||||||
-- >>> lookup (name "foo") shadowed
|
-- >>> lookup (name "foo") shadowed
|
||||||
@ -115,19 +118,19 @@ trim (Environment (a :| as)) = Environment (a :| filtered)
|
|||||||
where filtered = filter (not . Map.null) as
|
where filtered = filter (not . Map.null) as
|
||||||
|
|
||||||
bind :: Foldable t => t Name -> Environment l a -> Environment l a
|
bind :: Foldable t => t Name -> Environment l a -> Environment l a
|
||||||
bind names env = foldMap envForName names
|
bind names env = fromList (mapMaybe lookupName (Prologue.toList names))
|
||||||
where envForName name = maybe mempty (curry unit name) (lookup name env)
|
where
|
||||||
|
lookupName name = (,) name <$> lookup name env
|
||||||
|
|
||||||
-- | Get all bound 'Name's in an environment.
|
-- | Get all bound 'Name's in an environment.
|
||||||
names :: Environment l a -> [Name]
|
names :: Environment l a -> [Name]
|
||||||
names = fmap fst . pairs
|
names = fmap fst . pairs
|
||||||
|
|
||||||
-- | Overwrite a set of key-value bindings in the provided environment.
|
-- | Lookup and alias name-value bindings from an environment.
|
||||||
overwrite :: [(Name, Name)] -> Environment l a -> Environment l a
|
overwrite :: [(Name, Name)] -> Environment l a -> Environment l a
|
||||||
overwrite pairs env = foldMap go pairs where
|
overwrite pairs env = fromList $ mapMaybe lookupAndAlias pairs
|
||||||
go (k, v) = case lookup k env of
|
where
|
||||||
Nothing -> mempty
|
lookupAndAlias (oldName, newName) = (,) newName <$> lookup oldName env
|
||||||
Just addr -> unit (v, addr)
|
|
||||||
|
|
||||||
-- | Retrieve the 'Live' set of addresses to which the given free variable names are bound.
|
-- | Retrieve the 'Live' set of addresses to which the given free variable names are bound.
|
||||||
--
|
--
|
||||||
|
@ -39,6 +39,7 @@ import Data.Abstract.ModuleTable as ModuleTable
|
|||||||
import Data.Abstract.Origin (SomeOrigin, packageOrigin)
|
import Data.Abstract.Origin (SomeOrigin, packageOrigin)
|
||||||
import Data.Abstract.Package as Package
|
import Data.Abstract.Package as Package
|
||||||
import Data.Language
|
import Data.Language
|
||||||
|
import Data.Empty as Empty
|
||||||
import Data.Scientific (Scientific)
|
import Data.Scientific (Scientific)
|
||||||
import Data.Semigroup.App
|
import Data.Semigroup.App
|
||||||
import Data.Semigroup.Foldable
|
import Data.Semigroup.Foldable
|
||||||
@ -220,12 +221,12 @@ load name = askModuleTable >>= maybeM notFound . ModuleTable.lookup name >>= eva
|
|||||||
where
|
where
|
||||||
notFound = throwLoadError (LoadError name)
|
notFound = throwLoadError (LoadError name)
|
||||||
|
|
||||||
evalAndCache [] = (,) mempty <$> unit
|
evalAndCache [] = (,) Empty.empty <$> unit
|
||||||
evalAndCache [x] = evalAndCache' x
|
evalAndCache [x] = evalAndCache' x
|
||||||
evalAndCache (x:xs) = do
|
evalAndCache (x:xs) = do
|
||||||
(env, _) <- evalAndCache' x
|
(env, _) <- evalAndCache' x
|
||||||
(env', v') <- evalAndCache xs
|
(env', v') <- evalAndCache xs
|
||||||
pure (env <> env', v')
|
pure (mergeEnvs env env', v')
|
||||||
|
|
||||||
evalAndCache' x = do
|
evalAndCache' x = do
|
||||||
let mPath = modulePath (moduleInfo x)
|
let mPath = modulePath (moduleInfo x)
|
||||||
@ -233,7 +234,7 @@ load name = askModuleTable >>= maybeM notFound . ModuleTable.lookup name >>= eva
|
|||||||
if mPath `elem` unLoadStack
|
if mPath `elem` unLoadStack
|
||||||
then do -- Circular load, don't keep evaluating.
|
then do -- Circular load, don't keep evaluating.
|
||||||
v <- trace ("load (skip evaluating, circular load): " <> show mPath) unit
|
v <- trace ("load (skip evaluating, circular load): " <> show mPath) unit
|
||||||
pure (mempty, v)
|
pure (Empty.empty, v)
|
||||||
else do
|
else do
|
||||||
modifyLoadStack (loadStackPush mPath)
|
modifyLoadStack (loadStackPush mPath)
|
||||||
v <- trace ("load (evaluating): " <> show mPath) $ evaluateModule x
|
v <- trace ("load (evaluating): " <> show mPath) $ evaluateModule x
|
||||||
@ -249,7 +250,7 @@ load name = askModuleTable >>= maybeM notFound . ModuleTable.lookup name >>= eva
|
|||||||
filterEnv :: Exports.Exports l a -> Environment l a -> Environment l a
|
filterEnv :: Exports.Exports l a -> Environment l a -> Environment l a
|
||||||
filterEnv ports env
|
filterEnv ports env
|
||||||
| Exports.null ports = env
|
| Exports.null ports = env
|
||||||
| otherwise = Exports.toEnvironment ports <> overwrite (Exports.aliases ports) env
|
| otherwise = Exports.toEnvironment ports `mergeEnvs` overwrite (Exports.aliases ports) env
|
||||||
|
|
||||||
|
|
||||||
-- | Evaluate a term to a value using the semantics of the current analysis.
|
-- | Evaluate a term to a value using the semantics of the current analysis.
|
||||||
|
@ -10,10 +10,9 @@ module Data.Abstract.Exports
|
|||||||
import Prelude hiding (null)
|
import Prelude hiding (null)
|
||||||
import Prologue hiding (null)
|
import Prologue hiding (null)
|
||||||
import Data.Abstract.Address
|
import Data.Abstract.Address
|
||||||
import Data.Abstract.Environment (Environment)
|
import Data.Abstract.Environment (Environment, unpairs)
|
||||||
import Data.Abstract.FreeVariables
|
import Data.Abstract.FreeVariables
|
||||||
import qualified Data.Map as Map
|
import qualified Data.Map as Map
|
||||||
import Data.Semigroup.Reducer
|
|
||||||
|
|
||||||
-- | A map of export names to an alias & address tuple.
|
-- | A map of export names to an alias & address tuple.
|
||||||
newtype Exports l a = Exports { unExports :: Map.Map Name (Name, Maybe (Address l a)) }
|
newtype Exports l a = Exports { unExports :: Map.Map Name (Name, Maybe (Address l a)) }
|
||||||
@ -23,9 +22,10 @@ null :: Exports l a -> Bool
|
|||||||
null = Map.null . unExports
|
null = Map.null . unExports
|
||||||
|
|
||||||
toEnvironment :: Exports l a -> Environment l a
|
toEnvironment :: Exports l a -> Environment l a
|
||||||
toEnvironment = Map.foldMapWithKey buildEnv . unExports where
|
toEnvironment exports = unpairs (mapMaybe collectExport (toList (unExports exports)))
|
||||||
buildEnv _ (_, Nothing) = mempty
|
where
|
||||||
buildEnv _ (n, Just a) = unit (n, a)
|
collectExport (_, Nothing) = Nothing
|
||||||
|
collectExport (n, Just a) = Just (n, a)
|
||||||
|
|
||||||
insert :: Name -> Name -> Maybe (Address l a) -> Exports l a -> Exports l a
|
insert :: Name -> Name -> Maybe (Address l a) -> Exports l a -> Exports l a
|
||||||
insert name alias address = Exports . Map.insert name (alias, address) . unExports
|
insert name alias address = Exports . Map.insert name (alias, address) . unExports
|
||||||
|
@ -10,6 +10,7 @@ import Control.Abstract.Analysis
|
|||||||
import Data.Abstract.Address
|
import Data.Abstract.Address
|
||||||
import Data.Abstract.Environment as Env
|
import Data.Abstract.Environment as Env
|
||||||
import Data.Align (alignWith)
|
import Data.Align (alignWith)
|
||||||
|
import qualified Data.Empty as Empty
|
||||||
import Data.Semigroup.Reducer (Reducer)
|
import Data.Semigroup.Reducer (Reducer)
|
||||||
import Prelude
|
import Prelude
|
||||||
import Prologue hiding (TypeError)
|
import Prologue hiding (TypeError)
|
||||||
@ -90,8 +91,8 @@ instance ( Alternative (m effects)
|
|||||||
tvar <- Var <$> raise fresh
|
tvar <- Var <$> raise fresh
|
||||||
assign a tvar
|
assign a tvar
|
||||||
(env, tvars) <- rest
|
(env, tvars) <- rest
|
||||||
pure (Env.insert name a env, tvar : tvars)) (pure mempty) names
|
pure (Env.insert name a env, tvar : tvars)) (pure (Empty.empty, Empty.empty)) names
|
||||||
ret <- localEnv (mappend env) body
|
ret <- localEnv (mergeEnvs env) body
|
||||||
pure (Product tvars :-> ret)
|
pure (Product tvars :-> ret)
|
||||||
|
|
||||||
unit = pure Unit
|
unit = pure Unit
|
||||||
@ -111,7 +112,7 @@ instance ( Alternative (m effects)
|
|||||||
klass _ _ _ = pure Object
|
klass _ _ _ = pure Object
|
||||||
namespace _ _ = pure Unit
|
namespace _ _ = pure Unit
|
||||||
|
|
||||||
scopedEnvironment _ = pure mempty
|
scopedEnvironment _ = pure Empty.empty
|
||||||
|
|
||||||
asString t = unify t String $> ""
|
asString t = unify t String $> ""
|
||||||
asPair t = do
|
asPair t = do
|
||||||
|
@ -230,12 +230,12 @@ instance ( Monad (m effects)
|
|||||||
|
|
||||||
klass n [] env = pure . injValue $ Class n env
|
klass n [] env = pure . injValue $ Class n env
|
||||||
klass n supers env = do
|
klass n supers env = do
|
||||||
product <- mconcat <$> traverse scopedEnvironment supers
|
product <- foldl mergeEnvs emptyEnv <$> traverse scopedEnvironment supers
|
||||||
pure . injValue $ Class n (Env.push product <> env)
|
pure . injValue $ Class n (mergeEnvs (Env.push product) env)
|
||||||
|
|
||||||
namespace n env = do
|
namespace n env = do
|
||||||
maybeAddr <- lookupEnv n
|
maybeAddr <- lookupEnv n
|
||||||
env' <- maybe (pure mempty) (asNamespaceEnv <=< deref) maybeAddr
|
env' <- maybe (pure emptyEnv) (asNamespaceEnv <=< deref) maybeAddr
|
||||||
pure (injValue (Namespace n (Env.mergeNewer env' env)))
|
pure (injValue (Namespace n (Env.mergeNewer env' env)))
|
||||||
where asNamespaceEnv v
|
where asNamespaceEnv v
|
||||||
| Just (Namespace _ env') <- prjValue v = pure env'
|
| Just (Namespace _ env') <- prjValue v = pure env'
|
||||||
@ -338,7 +338,7 @@ instance ( Monad (m effects)
|
|||||||
a <- alloc name
|
a <- alloc name
|
||||||
assign a v
|
assign a v
|
||||||
Env.insert name a <$> rest) (pure env) (zip names params)
|
Env.insert name a <$> rest) (pure env) (zip names params)
|
||||||
localEnv (mappend bindings) (evalClosure label)
|
localEnv (mergeEnvs bindings) (evalClosure label)
|
||||||
Nothing -> throwValueError (CallError op)
|
Nothing -> throwValueError (CallError op)
|
||||||
where
|
where
|
||||||
evalClosure :: Label -> m effects (Value location)
|
evalClosure :: Label -> m effects (Value location)
|
||||||
|
@ -195,7 +195,7 @@ instance Show1 MemberAccess where liftShowsPrec = genericLiftShowsPrec
|
|||||||
instance Evaluatable MemberAccess where
|
instance Evaluatable MemberAccess where
|
||||||
eval (fmap subtermValue -> MemberAccess mem acc) = do
|
eval (fmap subtermValue -> MemberAccess mem acc) = do
|
||||||
lhs <- mem >>= scopedEnvironment
|
lhs <- mem >>= scopedEnvironment
|
||||||
localEnv (mappend lhs) acc
|
localEnv (mergeEnvs lhs) acc
|
||||||
|
|
||||||
-- | Subscript (e.g a[1])
|
-- | Subscript (e.g a[1])
|
||||||
data Subscript a
|
data Subscript a
|
||||||
|
@ -104,7 +104,7 @@ instance Evaluatable Assignment where
|
|||||||
modifyEnv (Env.insert name addr) $> v
|
modifyEnv (Env.insert name addr) $> v
|
||||||
_ -> do
|
_ -> do
|
||||||
lhs <- subtermValue assignmentTarget >>= scopedEnvironment
|
lhs <- subtermValue assignmentTarget >>= scopedEnvironment
|
||||||
localEnv (mappend lhs) (subtermValue assignmentValue)
|
localEnv (mergeEnvs lhs) (subtermValue assignmentValue)
|
||||||
|
|
||||||
-- | Post increment operator (e.g. 1++ in Go, or i++ in C).
|
-- | Post increment operator (e.g. 1++ in Go, or i++ in C).
|
||||||
newtype PostIncrement a = PostIncrement a
|
newtype PostIncrement a = PostIncrement a
|
||||||
|
@ -60,7 +60,7 @@ instance Evaluatable Import where
|
|||||||
paths <- resolveGoImport importPath
|
paths <- resolveGoImport importPath
|
||||||
for_ paths $ \path -> do
|
for_ paths $ \path -> do
|
||||||
(importedEnv, _) <- traceResolve (unPath importPath) path $ isolate (require path)
|
(importedEnv, _) <- traceResolve (unPath importPath) path $ isolate (require path)
|
||||||
modifyEnv (mappend importedEnv)
|
modifyEnv (mergeEnvs importedEnv)
|
||||||
unit
|
unit
|
||||||
|
|
||||||
|
|
||||||
@ -81,9 +81,9 @@ instance Evaluatable QualifiedImport where
|
|||||||
void $ letrec' alias $ \addr -> do
|
void $ letrec' alias $ \addr -> do
|
||||||
for_ paths $ \path -> do
|
for_ paths $ \path -> do
|
||||||
(importedEnv, _) <- traceResolve (unPath importPath) path $ isolate (require path)
|
(importedEnv, _) <- traceResolve (unPath importPath) path $ isolate (require path)
|
||||||
modifyEnv (mappend importedEnv)
|
modifyEnv (mergeEnvs importedEnv)
|
||||||
|
|
||||||
makeNamespace alias addr []
|
makeNamespace alias addr Nothing
|
||||||
unit
|
unit
|
||||||
|
|
||||||
-- | Side effect only imports (no symbols made available to the calling environment).
|
-- | Side effect only imports (no symbols made available to the calling environment).
|
||||||
|
@ -50,7 +50,7 @@ include pathTerm f = do
|
|||||||
name <- subtermValue pathTerm >>= asString
|
name <- subtermValue pathTerm >>= asString
|
||||||
path <- resolvePHPName name
|
path <- resolvePHPName name
|
||||||
(importedEnv, v) <- traceResolve name path $ isolate (f path)
|
(importedEnv, v) <- traceResolve name path $ isolate (f path)
|
||||||
modifyEnv (mappend importedEnv)
|
modifyEnv (mergeEnvs importedEnv)
|
||||||
pure v
|
pure v
|
||||||
|
|
||||||
newtype Require a = Require a
|
newtype Require a = Require a
|
||||||
@ -190,7 +190,7 @@ instance Show1 QualifiedName where liftShowsPrec = genericLiftShowsPrec
|
|||||||
instance Evaluatable QualifiedName where
|
instance Evaluatable QualifiedName where
|
||||||
eval (fmap subtermValue -> QualifiedName name iden) = do
|
eval (fmap subtermValue -> QualifiedName name iden) = do
|
||||||
lhs <- name >>= scopedEnvironment
|
lhs <- name >>= scopedEnvironment
|
||||||
localEnv (mappend lhs) iden
|
localEnv (mergeEnvs lhs) iden
|
||||||
|
|
||||||
|
|
||||||
newtype NamespaceName a = NamespaceName (NonEmpty a)
|
newtype NamespaceName a = NamespaceName (NonEmpty a)
|
||||||
@ -205,7 +205,7 @@ instance Evaluatable NamespaceName where
|
|||||||
where
|
where
|
||||||
f ns nam = do
|
f ns nam = do
|
||||||
env <- ns >>= scopedEnvironment
|
env <- ns >>= scopedEnvironment
|
||||||
localEnv (mappend env) nam
|
localEnv (mergeEnvs env) nam
|
||||||
|
|
||||||
newtype ConstDeclaration a = ConstDeclaration [a]
|
newtype ConstDeclaration a = ConstDeclaration [a]
|
||||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||||
@ -366,10 +366,10 @@ instance Evaluatable Namespace where
|
|||||||
go [] = raise (fail "expected at least one free variable in namespaceName, found none")
|
go [] = raise (fail "expected at least one free variable in namespaceName, found none")
|
||||||
-- The last name creates a closure over the namespace body.
|
-- The last name creates a closure over the namespace body.
|
||||||
go [name] = letrec' name $ \addr ->
|
go [name] = letrec' name $ \addr ->
|
||||||
subtermValue namespaceBody *> makeNamespace name addr []
|
subtermValue namespaceBody *> makeNamespace name addr Nothing
|
||||||
-- Each namespace name creates a closure over the subsequent namespace closures
|
-- Each namespace name creates a closure over the subsequent namespace closures
|
||||||
go (name:xs) = letrec' name $ \addr ->
|
go (name:xs) = letrec' name $ \addr ->
|
||||||
go xs <* makeNamespace name addr []
|
go xs <* makeNamespace name addr Nothing
|
||||||
|
|
||||||
data TraitDeclaration a = TraitDeclaration { traitName :: a, traitStatements :: [a] }
|
data TraitDeclaration a = TraitDeclaration { traitName :: a, traitStatements :: [a] }
|
||||||
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||||
|
@ -101,7 +101,7 @@ instance Evaluatable Import where
|
|||||||
-- Last module path is the one we want to import
|
-- Last module path is the one we want to import
|
||||||
let path = NonEmpty.last modulePaths
|
let path = NonEmpty.last modulePaths
|
||||||
(importedEnv, _) <- isolate (require path)
|
(importedEnv, _) <- isolate (require path)
|
||||||
modifyEnv (mappend (select importedEnv))
|
modifyEnv (mergeEnvs (select importedEnv))
|
||||||
unit
|
unit
|
||||||
where
|
where
|
||||||
select importedEnv
|
select importedEnv
|
||||||
@ -126,14 +126,14 @@ instance Evaluatable QualifiedImport where
|
|||||||
-- Evaluate and import the last module, updating the environment
|
-- Evaluate and import the last module, updating the environment
|
||||||
go ((name, path) :| []) = letrec' name $ \addr -> do
|
go ((name, path) :| []) = letrec' name $ \addr -> do
|
||||||
(importedEnv, _) <- isolate (require path)
|
(importedEnv, _) <- isolate (require path)
|
||||||
modifyEnv (mappend importedEnv)
|
modifyEnv (mergeEnvs importedEnv)
|
||||||
void $ makeNamespace name addr []
|
void $ makeNamespace name addr Nothing
|
||||||
unit
|
unit
|
||||||
-- Evaluate each parent module, creating a just namespace
|
-- Evaluate each parent module, creating a just namespace
|
||||||
go ((name, path) :| xs) = letrec' name $ \addr -> do
|
go ((name, path) :| xs) = letrec' name $ \addr -> do
|
||||||
void $ isolate (require path)
|
void $ isolate (require path)
|
||||||
void $ go (NonEmpty.fromList xs)
|
void $ go (NonEmpty.fromList xs)
|
||||||
makeNamespace name addr []
|
makeNamespace name addr Nothing
|
||||||
|
|
||||||
data QualifiedAliasedImport a = QualifiedAliasedImport { qualifiedAliasedImportFrom :: QualifiedName, qualifiedAliasedImportAlias :: !a }
|
data QualifiedAliasedImport a = QualifiedAliasedImport { qualifiedAliasedImportFrom :: QualifiedName, qualifiedAliasedImportAlias :: !a }
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||||
@ -155,8 +155,8 @@ instance Evaluatable QualifiedAliasedImport where
|
|||||||
letrec' alias $ \addr -> do
|
letrec' alias $ \addr -> do
|
||||||
let path = NonEmpty.last modulePaths
|
let path = NonEmpty.last modulePaths
|
||||||
(importedEnv, _) <- isolate (require path)
|
(importedEnv, _) <- isolate (require path)
|
||||||
modifyEnv (mappend importedEnv)
|
modifyEnv (mergeEnvs importedEnv)
|
||||||
void $ makeNamespace alias addr []
|
void $ makeNamespace alias addr Nothing
|
||||||
unit
|
unit
|
||||||
|
|
||||||
-- | Ellipsis (used in splice expressions and alternatively can be used as a fill in expression, like `undefined` in Haskell)
|
-- | Ellipsis (used in splice expressions and alternatively can be used as a fill in expression, like `undefined` in Haskell)
|
||||||
|
@ -218,11 +218,13 @@ endBlock :: Assignment
|
|||||||
endBlock = makeTerm <$> symbol EndBlock <*> children (Statement.ScopeExit <$> many expression)
|
endBlock = makeTerm <$> symbol EndBlock <*> children (Statement.ScopeExit <$> many expression)
|
||||||
|
|
||||||
class' :: Assignment
|
class' :: Assignment
|
||||||
class' = makeTerm <$> symbol Class <*> (withNewScope . children) (Ruby.Syntax.Class <$> expression <*> (superclass <|> pure []) <*> expressions)
|
class' = makeTerm <$> symbol Class <*> (withNewScope . children) (Ruby.Syntax.Class <$> expression <*> optional superclass <*> expressions)
|
||||||
where superclass = pure <$ symbol Superclass <*> children expression
|
where
|
||||||
|
superclass :: Assignment
|
||||||
|
superclass = symbol Superclass *> children expression
|
||||||
|
|
||||||
singletonClass :: Assignment
|
singletonClass :: Assignment
|
||||||
singletonClass = makeTerm <$> symbol SingletonClass <*> (withNewScope . children) (Ruby.Syntax.Class <$> expression <*> pure [] <*> expressions)
|
singletonClass = makeTerm <$> symbol SingletonClass <*> (withNewScope . children) (Ruby.Syntax.Class <$> expression <*> pure Nothing <*> expressions)
|
||||||
|
|
||||||
module' :: Assignment
|
module' :: Assignment
|
||||||
module' = makeTerm <$> symbol Module <*> (withNewScope . children) (Ruby.Syntax.Module <$> expression <*> many expression)
|
module' = makeTerm <$> symbol Module <*> (withNewScope . children) (Ruby.Syntax.Module <$> expression <*> many expression)
|
||||||
|
@ -50,7 +50,7 @@ instance Evaluatable Send where
|
|||||||
func <- case sendReceiver of
|
func <- case sendReceiver of
|
||||||
Just recv -> do
|
Just recv -> do
|
||||||
recvEnv <- subtermValue recv >>= scopedEnvironment
|
recvEnv <- subtermValue recv >>= scopedEnvironment
|
||||||
localEnv (mappend recvEnv) sel
|
localEnv (mergeEnvs recvEnv) sel
|
||||||
Nothing -> sel -- TODO Does this require `localize` so we don't leak terms when resolving `sendSelector`?
|
Nothing -> sel -- TODO Does this require `localize` so we don't leak terms when resolving `sendSelector`?
|
||||||
|
|
||||||
call func (map subtermValue sendArgs) -- TODO pass through sendBlock
|
call func (map subtermValue sendArgs) -- TODO pass through sendBlock
|
||||||
@ -101,13 +101,12 @@ doLoad :: MonadEvaluatable location term value effects m => ByteString -> Bool -
|
|||||||
doLoad path shouldWrap = do
|
doLoad path shouldWrap = do
|
||||||
path' <- resolveRubyPath path
|
path' <- resolveRubyPath path
|
||||||
(importedEnv, _) <- traceResolve path path' $ isolate (load path')
|
(importedEnv, _) <- traceResolve path path' $ isolate (load path')
|
||||||
unless shouldWrap $ modifyEnv (mappend importedEnv)
|
unless shouldWrap $ modifyEnv (mergeEnvs importedEnv)
|
||||||
boolean Prelude.True -- load always returns true. http://ruby-doc.org/core-2.5.0/Kernel.html#method-i-load
|
boolean Prelude.True -- load always returns true. http://ruby-doc.org/core-2.5.0/Kernel.html#method-i-load
|
||||||
|
|
||||||
-- TODO: autoload
|
-- TODO: autoload
|
||||||
|
|
||||||
|
data Class a = Class { classIdentifier :: !a, classSuperClass :: !(Maybe a), classBody :: !a }
|
||||||
data Class a = Class { classIdentifier :: !a, classSuperClasses :: ![a], classBody :: !a }
|
|
||||||
deriving (Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
deriving (Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||||
|
|
||||||
instance Diffable Class where
|
instance Diffable Class where
|
||||||
@ -119,10 +118,10 @@ instance Show1 Class where liftShowsPrec = genericLiftShowsPrec
|
|||||||
|
|
||||||
instance Evaluatable Class where
|
instance Evaluatable Class where
|
||||||
eval Class{..} = do
|
eval Class{..} = do
|
||||||
supers <- traverse subtermValue classSuperClasses
|
super <- traverse subtermValue classSuperClass
|
||||||
name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm classIdentifier)
|
name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm classIdentifier)
|
||||||
letrec' name $ \addr ->
|
letrec' name $ \addr ->
|
||||||
subtermValue classBody <* makeNamespace name addr supers
|
subtermValue classBody <* makeNamespace name addr super
|
||||||
|
|
||||||
data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] }
|
data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] }
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||||
@ -135,7 +134,7 @@ instance Evaluatable Module where
|
|||||||
eval (Module iden xs) = do
|
eval (Module iden xs) = do
|
||||||
name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm iden)
|
name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm iden)
|
||||||
letrec' name $ \addr ->
|
letrec' name $ \addr ->
|
||||||
eval xs <* makeNamespace name addr []
|
eval xs <* makeNamespace name addr Nothing
|
||||||
|
|
||||||
data LowPrecedenceBoolean a
|
data LowPrecedenceBoolean a
|
||||||
= LowAnd !a !a
|
= LowAnd !a !a
|
||||||
|
@ -95,8 +95,8 @@ javascriptExtensions = ["js"]
|
|||||||
evalRequire :: MonadEvaluatable location term value effects m => ModulePath -> Name -> m effects value
|
evalRequire :: MonadEvaluatable location term value effects m => ModulePath -> Name -> m effects value
|
||||||
evalRequire modulePath alias = letrec' alias $ \addr -> do
|
evalRequire modulePath alias = letrec' alias $ \addr -> do
|
||||||
(importedEnv, _) <- isolate (require modulePath)
|
(importedEnv, _) <- isolate (require modulePath)
|
||||||
modifyEnv (mappend importedEnv)
|
modifyEnv (mergeEnvs importedEnv)
|
||||||
void $ makeNamespace alias addr []
|
void $ makeNamespace alias addr Nothing
|
||||||
unit
|
unit
|
||||||
|
|
||||||
data Import a = Import { importSymbols :: ![(Name, Name)], importFrom :: ImportPath }
|
data Import a = Import { importSymbols :: ![(Name, Name)], importFrom :: ImportPath }
|
||||||
@ -111,7 +111,7 @@ instance Evaluatable Import where
|
|||||||
eval (Import symbols importPath) = do
|
eval (Import symbols importPath) = do
|
||||||
modulePath <- resolveWithNodejsStrategy importPath typescriptExtensions
|
modulePath <- resolveWithNodejsStrategy importPath typescriptExtensions
|
||||||
(importedEnv, _) <- isolate (require modulePath)
|
(importedEnv, _) <- isolate (require modulePath)
|
||||||
modifyEnv (mappend (renamed importedEnv)) *> unit
|
modifyEnv (mergeEnvs (renamed importedEnv)) *> unit
|
||||||
where
|
where
|
||||||
renamed importedEnv
|
renamed importedEnv
|
||||||
| Prologue.null symbols = importedEnv
|
| Prologue.null symbols = importedEnv
|
||||||
@ -609,7 +609,7 @@ instance Evaluatable Module where
|
|||||||
eval (Module iden xs) = do
|
eval (Module iden xs) = do
|
||||||
name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm iden)
|
name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm iden)
|
||||||
letrec' name $ \addr ->
|
letrec' name $ \addr ->
|
||||||
eval xs <* makeNamespace name addr []
|
eval xs <* makeNamespace name addr Nothing
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
@ -624,7 +624,7 @@ instance Evaluatable InternalModule where
|
|||||||
eval (InternalModule iden xs) = do
|
eval (InternalModule iden xs) = do
|
||||||
name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm iden)
|
name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm iden)
|
||||||
letrec' name $ \addr ->
|
letrec' name $ \addr ->
|
||||||
eval xs <* makeNamespace name addr []
|
eval xs <* makeNamespace name addr Nothing
|
||||||
|
|
||||||
instance Declarations a => Declarations (InternalModule a) where
|
instance Declarations a => Declarations (InternalModule a) where
|
||||||
declaredName InternalModule{..} = declaredName internalModuleIdentifier
|
declaredName InternalModule{..} = declaredName internalModuleIdentifier
|
||||||
|
@ -30,7 +30,7 @@ spec = parallel $ do
|
|||||||
|
|
||||||
it "side effect only imports" $ do
|
it "side effect only imports" $ do
|
||||||
env <- environment . snd <$> evaluate "main2.ts"
|
env <- environment . snd <$> evaluate "main2.ts"
|
||||||
env `shouldBe` mempty
|
env `shouldBe` emptyEnv
|
||||||
|
|
||||||
it "fails exporting symbols not defined in the module" $ do
|
it "fails exporting symbols not defined in the module" $ do
|
||||||
v <- fst <$> evaluate "bad-export.ts"
|
v <- fst <$> evaluate "bad-export.ts"
|
||||||
|
Loading…
Reference in New Issue
Block a user