Skip to content

Commit 0014960

Browse files
committed
CESK fix for imports
1 parent e3de42b commit 0014960

File tree

3 files changed

+23
-8
lines changed

3 files changed

+23
-8
lines changed

src/swarm-engine/Swarm/Game/CESK.hs

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -95,7 +95,7 @@ import Swarm.Game.Ingredients (Count)
9595
import Swarm.Game.Tick
9696
import Swarm.Game.World (WorldUpdate (..))
9797
import Swarm.Language.Elaborate (insertSuspend)
98-
import Swarm.Language.Load (SourceMap, SyntaxWithImports (..))
98+
import Swarm.Language.Load (SyntaxWithImports (..))
9999
import Swarm.Language.Requirements.Type (Requirements)
100100
import Swarm.Language.Syntax
101101
import Swarm.Language.Types
@@ -153,6 +153,9 @@ data Frame
153153
-- in the given environment (extended by binding the variable,
154154
-- if there is one, to the output of the first command).
155155
FBind (Maybe Var) (Maybe (Polytype, Requirements)) (Term Resolved) Env
156+
| -- | We are in the process of evaluating an import; once done, we
157+
-- should proceed to evaluate the given body.
158+
FImport (Term Resolved)
156159
| -- | Apply specific updates to the world and current robot.
157160
--
158161
-- The 'Const' is used to track the original command for error messages.
@@ -425,6 +428,7 @@ prettyFrame f (p, inner) = case f of
425428
FExec -> prettyPrefix "" (p, inner)
426429
FBind Nothing _ t _ -> (0, pparens (p < 1) inner <+> ";" <+> ppr t)
427430
FBind (Just x) _ t _ -> (0, hsep [ppr x, "<-", pparens (p < 1) inner, ";", ppr t])
431+
FImport t -> (11, hsep ["import", inner, "in", ppr t])
428432
FImmediate c _worldUpds _robotUpds -> prettyPrefix ("I[" <> ppr c <> "") (p, inner)
429433
FUpdate {} -> (p, inner)
430434
FFinishAtomic -> prettyPrefix "" (p, inner)

src/swarm-engine/Swarm/Game/State.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -132,7 +132,7 @@ import Swarm.Game.World qualified as W
132132
import Swarm.Game.World.Coords
133133
import Swarm.Language.Load (SyntaxWithImports (..))
134134
import Swarm.Language.Pipeline (processSource, requireNonEmptyTerm)
135-
import Swarm.Language.Syntax (Phase (..), SrcLoc (..), Syntax, sLoc)
135+
import Swarm.Language.Syntax (Phase (..), SrcLoc (..), sLoc)
136136
import Swarm.Language.Value (Env)
137137
import Swarm.Log
138138
import Swarm.Util (applyWhen, uniq)

src/swarm-engine/Swarm/Game/Step.hs

Lines changed: 17 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -739,12 +739,9 @@ stepCESK cesk = case cesk of
739739
-- To evaluate an import:
740740
-- (1) stick a 'suspend' at the end of the term
741741
-- corresponding to the imported module, so we can save the resulting environment
742-
-- (2) push an FBind frame on the stack to continue with the
743-
-- rest of the code once we're done processing the import.
744-
-- Note that the environment in the FBind will be ignored
745-
-- in favor of the environment resulting from the suspend.
746-
-- (3) push an FExec frame to execute the import itself.
747-
Just m -> In (insertSuspend $ erase m ^. sTerm) e s (FExec : FBind Nothing Nothing t e : k)
742+
-- (2) push an FImport frame on the stack to continue with the
743+
-- body in the context of the input once we're done processing it.
744+
Just m -> In (insertSuspend $ erase m ^. sTerm) e s (FImport t : k)
748745
-- XXX keep a map from imports to corresponding Env, don't re-evaluate if it's already
749746
-- in the map. To make this sound, need to disallow all but defs in an import.
750747
-- Ignore explicit parens.
@@ -817,6 +814,16 @@ stepCESK cesk = case cesk of
817814
Nothing -> addValueBinding x v e
818815
Just (ty, reqs) -> addBinding x (WithType v ty reqs) e
819816
return $ In t2 e' s (FExec : k)
817+
-- If we have suspended at the end of an import, go ahead and
818+
-- evaluate the suspend without waiting for an FExec, since the body
819+
-- of the import may or may not be something we need to execute
820+
-- (e.g. "import blah in x + 1" vs "import blah in move; foo")
821+
Out (VSuspend t e) s (FImport body : k) -> return $ In t e s (FSuspend e : FImport body : k)
822+
-- This case shouldn't happen: we will always insert a call to
823+
-- 'suspend' at the end of an import, so we will reach the 'FImport'
824+
-- frame in a 'Suspended' state, so we can restore the suspended
825+
-- environment.
826+
Out _ s (FImport _ : _) -> badMachineState s "FImport frame in non-suspended state"
820827
-- To execute a suspend instruction, evaluate its argument and then
821828
-- suspend.
822829
Out (VSuspend t e) s (FExec : k) -> return $ In t e s (FSuspend e : k)
@@ -852,6 +859,10 @@ stepCESK cesk = case cesk of
852859
Nothing -> addValueBinding x v e
853860
Just (ty, reqs) -> addBinding x (WithType v ty reqs) e
854861
return $ In t2 e' s (FExec : k)
862+
-- If we we're suspended after processing an import, resume by
863+
-- evaluating the body of the import in the suspended context we got
864+
-- after processing the import.
865+
Suspended _ e s (FImport t : k) -> return $ In t e s k
855866
-- Otherwise, if we're suspended with nothing else left to do,
856867
-- return the machine unchanged (but throw away the rest of the
857868
-- continuation stack).

0 commit comments

Comments
 (0)