mirror of
https://github.com/github/semantic.git
synced 2024-11-24 17:04:47 +03:00
Rename lambda to closure.
This commit is contained in:
parent
d9084f9f45
commit
97915e1410
@ -138,10 +138,10 @@ class Show value => AbstractValue location value effects where
|
|||||||
scopedEnvironment :: value -> Evaluator location term value effects (Maybe (Environment location value))
|
scopedEnvironment :: value -> Evaluator location term value effects (Maybe (Environment location value))
|
||||||
|
|
||||||
-- | Build a closure (a binder like a lambda or method definition).
|
-- | Build a closure (a binder like a lambda or method definition).
|
||||||
lambda :: [Name] -- ^ The parameter names.
|
closure :: [Name] -- ^ The parameter names.
|
||||||
-> Set Name -- ^ The set of free variables to close over.
|
-> Set Name -- ^ The set of free variables to close over.
|
||||||
-> Evaluator location term value effects value -- ^ The evaluator for the body of the closure.
|
-> Evaluator location term value effects value -- ^ The evaluator for the body of the closure.
|
||||||
-> Evaluator location term value effects value
|
-> Evaluator location term value effects value
|
||||||
-- | Evaluate an application (like a function call).
|
-- | Evaluate an application (like a function call).
|
||||||
call :: value -> [Evaluator location term value effects value] -> Evaluator location term value effects value
|
call :: value -> [Evaluator location term value effects value] -> Evaluator location term value effects value
|
||||||
|
|
||||||
|
@ -92,7 +92,7 @@ instance ( Addressable location effects
|
|||||||
, Reducer (Type location) (Cell location (Type location))
|
, Reducer (Type location) (Cell location (Type location))
|
||||||
)
|
)
|
||||||
=> AbstractValue location (Type location) effects where
|
=> AbstractValue location (Type location) effects where
|
||||||
lambda names _ body = do
|
closure names _ body = do
|
||||||
(env, tvars) <- foldr (\ name rest -> do
|
(env, tvars) <- foldr (\ name rest -> do
|
||||||
a <- alloc name
|
a <- alloc name
|
||||||
tvar <- Var <$> raise fresh
|
tvar <- Var <$> raise fresh
|
||||||
|
@ -349,7 +349,7 @@ instance ( Addressable location (Goto effects (Value location) ': effects)
|
|||||||
| otherwise = throwValueError (Bitwise2Error left right)
|
| otherwise = throwValueError (Bitwise2Error left right)
|
||||||
where pair = (left, right)
|
where pair = (left, right)
|
||||||
|
|
||||||
lambda parameters freeVariables body = do
|
closure parameters freeVariables body = do
|
||||||
l <- label body
|
l <- label body
|
||||||
injValue . Closure parameters l . Env.bind (foldr Set.delete freeVariables parameters) <$> getEnv
|
injValue . Closure parameters l . Env.bind (foldr Set.delete freeVariables parameters) <$> getEnv
|
||||||
|
|
||||||
|
@ -23,7 +23,7 @@ instance Show1 Function where liftShowsPrec = genericLiftShowsPrec
|
|||||||
instance Evaluatable Function where
|
instance Evaluatable Function where
|
||||||
eval Function{..} = do
|
eval Function{..} = do
|
||||||
name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm functionName)
|
name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm functionName)
|
||||||
(v, addr) <- letrec name (lambda (paramNames functionParameters) (Set.fromList (freeVariables functionBody)) (subtermValue functionBody))
|
(v, addr) <- letrec name (closure (paramNames functionParameters) (Set.fromList (freeVariables functionBody)) (subtermValue functionBody))
|
||||||
modifyEnv (Env.insert name addr)
|
modifyEnv (Env.insert name addr)
|
||||||
pure v
|
pure v
|
||||||
where paramNames = foldMap (freeVariables . subterm)
|
where paramNames = foldMap (freeVariables . subterm)
|
||||||
@ -47,7 +47,7 @@ instance Show1 Method where liftShowsPrec = genericLiftShowsPrec
|
|||||||
instance Evaluatable Method where
|
instance Evaluatable Method where
|
||||||
eval Method{..} = do
|
eval Method{..} = do
|
||||||
name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm methodName)
|
name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm methodName)
|
||||||
(v, addr) <- letrec name (lambda (paramNames methodParameters) (Set.fromList (freeVariables methodBody)) (subtermValue methodBody))
|
(v, addr) <- letrec name (closure (paramNames methodParameters) (Set.fromList (freeVariables methodBody)) (subtermValue methodBody))
|
||||||
modifyEnv (Env.insert name addr)
|
modifyEnv (Env.insert name addr)
|
||||||
pure v
|
pure v
|
||||||
where paramNames = foldMap (freeVariables . subterm)
|
where paramNames = foldMap (freeVariables . subterm)
|
||||||
|
@ -22,7 +22,7 @@ spec = parallel $ do
|
|||||||
|
|
||||||
it "calls functions" $ do
|
it "calls functions" $ do
|
||||||
(expected, _) <- evaluate $ do
|
(expected, _) <- evaluate $ do
|
||||||
identity <- lambda [name "x"] lowerBound (variable (name "x"))
|
identity <- closure [name "x"] lowerBound (variable (name "x"))
|
||||||
call identity [integer 123]
|
call identity [integer 123]
|
||||||
expected `shouldBe` Right (Value.injValue (Value.Integer (Number.Integer 123)))
|
expected `shouldBe` Right (Value.injValue (Value.Integer (Number.Integer 123)))
|
||||||
|
|
||||||
|
Loading…
Reference in New Issue
Block a user