swarm-0.2.0.0: 2D resource gathering game with programmable robots
CopyrightBrent Yorgey
LicenseBSD-3-Clause
Maintainerbyorgey@gmail.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

Swarm.Game.CESK

Description

The Swarm interpreter uses a technique known as a CESK machine (if you want to read up on them, you may want to start by reading about CEK machines first). Execution happens simply by iterating a step function, sending one state of the CESK machine to the next. In addition to being relatively efficient, this means we can easily run a bunch of robots synchronously, in parallel, without resorting to any threads (by stepping their machines in a round-robin fashion); pause and single-step the game; save and resume, and so on.

Essentially, a CESK machine state has four components:

  • The Control is the thing we are currently focused on: either a Term to evaluate, or a Value that we have just finished evaluating.
  • The Environment (Env) is a mapping from variables that might occur free in the Control to their values.
  • The Store (Store) is a mapping from abstract integer locations to values. We use it to store delayed (lazy) values, so they will be computed at most once.
  • The Kontinuation (Cont) is a stack of Frames, representing the evaluation context, i.e. what we are supposed to do after we finish with the currently focused thing. When we reduce the currently focused term to a value, the top frame on the stack tells us how to proceed.

You can think of a CESK machine as a defunctionalization of a recursive big-step interpreter, where we explicitly keep track of the call stack and the environments that would be in effect at various places in the recursion. One could probably even derive this mechanically, by writing a recursive big-step interpreter, then converting it to CPS, then defunctionalizing the continuations.

The slightly confusing thing about CESK machines is how we have to pass around environments everywhere. Basically, anywhere there can be unevaluated terms containing free variables (in values, in continuation stack frames, ...), we have to store the proper environment alongside so that when we eventually get around to evaluating it, we will be able to pull out the environment to use.

Synopsis

Frames and continuations

data Frame Source #

A frame is a single component of a continuation stack, explaining what to do next after we finish evaluating the currently focused term.

Constructors

FSnd Term Env

We were evaluating the first component of a pair; next, we should evaluate the second component which was saved in this frame (and push a FFst frame on the stack to save the first component).

FFst Value

We were evaluating the second component of a pair; when done, we should combine it with the value of the first component saved in this frame to construct a fully evaluated pair.

FArg Term Env

FArg t e says that we were evaluating the left-hand side of an application, so the next thing we should do is evaluate the term t (the right-hand side, i.e. argument of the application) in environment e. We will also push an FApp frame on the stack.

FApp Value

FApp v says that we were evaluating the right-hand side of an application; once we are done, we should pass the resulting value as an argument to v.

FLet Var Term Env

FLet x t2 e says that we were evaluating a term t1 in an expression of the form let x = t1 in t2, that is, we were evaluating the definition of x; the next thing we should do is evaluate t2 in the environment e extended with a binding for x.

FTry Value

We are executing inside a Try block. If an exception is raised, we will execute the stored term (the "catch" block).

FUnionEnv Env

We were executing a command; next we should take any environment it returned and union it with this one to produce the result of a bind expression.

FLoadEnv TCtx ReqCtx

We were executing a command that might have definitions; next we should take the resulting Env and add it to the robot's robotEnv, along with adding this accompanying Ctx and ReqCtx to the robot's robotCtx.

FDef Var

We were executing a definition; next we should take the resulting value and return a context binding the variable to the value.

FExec

An FExec frame means the focused value is a command, which we should now execute.

FBind (Maybe Var) Term Env

We are in the process of executing the first component of a bind; once done, we should also execute the second component in the given environment (extended by binding the variable, if there is one, to the output of the first command).

FImmediate WorldUpdate RobotUpdate

Apply specific updates to the world and current robot.

FUpdate Loc

Update the memory cell at a certain location with the computed value.

FFinishAtomic

Signal that we are done with an atomic computation.

Instances

Instances details
FromJSON Frame Source # 
Instance details

Defined in Swarm.Game.CESK

ToJSON Frame Source # 
Instance details

Defined in Swarm.Game.CESK

Generic Frame Source # 
Instance details

Defined in Swarm.Game.CESK

Associated Types

type Rep Frame :: Type -> Type #

Methods

from :: Frame -> Rep Frame x #

to :: Rep Frame x -> Frame #

Show Frame Source # 
Instance details

Defined in Swarm.Game.CESK

Methods

showsPrec :: Int -> Frame -> ShowS #

show :: Frame -> String #

showList :: [Frame] -> ShowS #

Eq Frame Source # 
Instance details

Defined in Swarm.Game.CESK

Methods

(==) :: Frame -> Frame -> Bool #

(/=) :: Frame -> Frame -> Bool #

type Rep Frame Source # 
Instance details

Defined in Swarm.Game.CESK

type Rep Frame = D1 ('MetaData "Frame" "Swarm.Game.CESK" "swarm-0.2.0.0-D1mAmWsUEjoFqpCaq9DHG0" 'False) (((C1 ('MetaCons "FSnd" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Term) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Env)) :+: (C1 ('MetaCons "FFst" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Value)) :+: C1 ('MetaCons "FArg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Term) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Env)))) :+: ((C1 ('MetaCons "FApp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Value)) :+: C1 ('MetaCons "FLet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Var) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Term) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Env)))) :+: (C1 ('MetaCons "FTry" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Value)) :+: C1 ('MetaCons "FUnionEnv" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Env))))) :+: ((C1 ('MetaCons "FLoadEnv" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TCtx) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ReqCtx)) :+: (C1 ('MetaCons "FDef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Var)) :+: C1 ('MetaCons "FExec" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "FBind" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Var)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Term) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Env))) :+: C1 ('MetaCons "FImmediate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 WorldUpdate) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 RobotUpdate))) :+: (C1 ('MetaCons "FUpdate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Loc)) :+: C1 ('MetaCons "FFinishAtomic" 'PrefixI 'False) (U1 :: Type -> Type)))))

type Cont = [Frame] Source #

A continuation is just a stack of frames.

Wrappers for creating delayed change of state

Store

data Store Source #

Store represents a store, indexing integer locations to Cells.

Instances

Instances details
FromJSON Store Source # 
Instance details

Defined in Swarm.Game.CESK

ToJSON Store Source # 
Instance details

Defined in Swarm.Game.CESK

Generic Store Source # 
Instance details

Defined in Swarm.Game.CESK

Associated Types

type Rep Store :: Type -> Type #

Methods

from :: Store -> Rep Store x #

to :: Rep Store x -> Store #

Show Store Source # 
Instance details

Defined in Swarm.Game.CESK

Methods

showsPrec :: Int -> Store -> ShowS #

show :: Store -> String #

showList :: [Store] -> ShowS #

Eq Store Source # 
Instance details

Defined in Swarm.Game.CESK

Methods

(==) :: Store -> Store -> Bool #

(/=) :: Store -> Store -> Bool #

type Rep Store Source # 
Instance details

Defined in Swarm.Game.CESK

type Rep Store = D1 ('MetaData "Store" "Swarm.Game.CESK" "swarm-0.2.0.0-D1mAmWsUEjoFqpCaq9DHG0" 'False) (C1 ('MetaCons "Store" 'PrefixI 'True) (S1 ('MetaSel ('Just "next") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Loc) :*: S1 ('MetaSel ('Just "mu") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (IntMap Cell))))

type Loc = Int Source #

data Cell Source #

A memory cell can be in one of three states.

Constructors

E Term Env

A cell starts out life as an unevaluated term together with its environment.

Blackhole Term Env

When the cell is Forced, it is set to a Blackhole while being evaluated. If it is ever referenced again while still a Blackhole, that means it depends on itself in a way that would trigger an infinite loop, and we can signal an error. (Of course, we <http://www.lel.ed.ac.uk/~gpullum/loopsnoop.html cannot detect all infinite loops this way>.)

A Blackhole saves the original Term and Env that are being evaluated; if Ctrl-C is used to cancel a computation while we are in the middle of evaluating a cell, the Blackhole can be reset to E.

V Value

Once evaluation is complete, we cache the final Value in the Cell, so that subsequent lookups can just use it without recomputing anything.

Instances

Instances details
FromJSON Cell Source # 
Instance details

Defined in Swarm.Game.CESK

ToJSON Cell Source # 
Instance details

Defined in Swarm.Game.CESK

Generic Cell Source # 
Instance details

Defined in Swarm.Game.CESK

Associated Types

type Rep Cell :: Type -> Type #

Methods

from :: Cell -> Rep Cell x #

to :: Rep Cell x -> Cell #

Show Cell Source # 
Instance details

Defined in Swarm.Game.CESK

Methods

showsPrec :: Int -> Cell -> ShowS #

show :: Cell -> String #

showList :: [Cell] -> ShowS #

Eq Cell Source # 
Instance details

Defined in Swarm.Game.CESK

Methods

(==) :: Cell -> Cell -> Bool #

(/=) :: Cell -> Cell -> Bool #

type Rep Cell Source # 
Instance details

Defined in Swarm.Game.CESK

allocate :: Env -> Term -> Store -> (Loc, Store) Source #

Allocate a new memory cell containing an unevaluated expression with the current environment. Return the index of the allocated cell.

lookupCell :: Loc -> Store -> Maybe Cell Source #

Look up the cell at a given index.

setCell :: Loc -> Cell -> Store -> Store Source #

Set the cell at a given index.

CESK machine states

data CESK Source #

The overall state of a CESK machine, which can actually be one of three kinds of states. The CESK machine is named after the first kind of state, and it would probably be possible to inline a bunch of things and get rid of the second state, but I find it much more natural and elegant this way. Most tutorial presentations of CEK/CESK machines only have one kind of state, but then again, most tutorial presentations only deal with the bare lambda calculus, so one can tell whether a term is a value just by seeing whether it is syntactically a lambda. I learned this approach from Harper's Practical Foundations of Programming Languages.

Constructors

In Term Env Store Cont

When we are on our way "in/down" into a term, we have a currently focused term to evaluate in the environment, a store, and a continuation. In this mode we generally pattern-match on the Term to decide what to do next.

Out Value Store Cont

Once we finish evaluating a term, we end up with a Value and we switch into "out" mode, bringing the value back up out of the depths to the context that was expecting it. In this mode we generally pattern-match on the Cont to decide what to do next.

Note that there is no Env, because we don't have anything with variables to evaluate at the moment, and we maintain the invariant that any unevaluated terms buried inside a Value or Cont must carry along their environment with them.

Up Exn Store Cont

An exception has been raised. Keep unwinding the continuation stack (until finding an enclosing Try in the case of a command failure or a user-generated exception, or until the stack is empty in the case of a fatal exception).

Waiting Integer CESK

The machine is waiting for the game to reach a certain time to resume its execution.

Instances

Instances details
FromJSON CESK Source # 
Instance details

Defined in Swarm.Game.CESK

ToJSON CESK Source # 
Instance details

Defined in Swarm.Game.CESK

Generic CESK Source # 
Instance details

Defined in Swarm.Game.CESK

Associated Types

type Rep CESK :: Type -> Type #

Methods

from :: CESK -> Rep CESK x #

to :: Rep CESK x -> CESK #

Show CESK Source # 
Instance details

Defined in Swarm.Game.CESK

Methods

showsPrec :: Int -> CESK -> ShowS #

show :: CESK -> String #

showList :: [CESK] -> ShowS #

Eq CESK Source # 
Instance details

Defined in Swarm.Game.CESK

Methods

(==) :: CESK -> CESK -> Bool #

(/=) :: CESK -> CESK -> Bool #

type Rep CESK Source # 
Instance details

Defined in Swarm.Game.CESK

type Rep CESK = D1 ('MetaData "CESK" "Swarm.Game.CESK" "swarm-0.2.0.0-D1mAmWsUEjoFqpCaq9DHG0" 'False) ((C1 ('MetaCons "In" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Term) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Env)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Store) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Cont))) :+: C1 ('MetaCons "Out" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Value) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Store) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Cont)))) :+: (C1 ('MetaCons "Up" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Exn) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Store) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Cont))) :+: C1 ('MetaCons "Waiting" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Integer) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CESK))))

Construction

initMachine :: ProcessedTerm -> Env -> Store -> CESK Source #

Initialize a machine state with a starting term along with its type; the term will be executed or just evaluated depending on whether it has a command type or not.

initMachine' :: ProcessedTerm -> Env -> Store -> Cont -> CESK Source #

Like initMachine, but also take an explicit starting continuation.

cancel :: CESK -> CESK Source #

Cancel the currently running computation.

resetBlackholes :: Store -> Store Source #

Reset any Blackholes in the Store. We need to use this any time a running computation is interrupted, either by an exception or by a Ctrl+C.

Extracting information

finalValue :: CESK -> Maybe (Value, Store) Source #

Is the CESK machine in a final (finished) state? If so, extract the final value and store.

Pretty-printing

prettyFrame :: Frame -> String Source #

Poor pretty-printing of frames.

prettyCont :: Cont -> String Source #

Poor pretty-printing of continuations.

prettyCESK :: CESK -> String Source #

Very poor pretty-printing of CESK machine states, really just for debugging. At some point we should make a nicer version.