License | BSD-3-Clause |
---|---|
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Values and environments used for interpreting the Swarm language.
Synopsis
- data Value where
- VUnit :: Value
- VInt :: Integer -> Value
- VText :: Text -> Value
- VDir :: Direction -> Value
- VBool :: Bool -> Value
- VRobot :: Int -> Value
- VInj :: Bool -> Value -> Value
- VPair :: Value -> Value -> Value
- VClo :: Var -> Term -> Env -> Value
- VCApp :: Const -> [Value] -> Value
- VBind :: Maybe Var -> Maybe Polytype -> Maybe Requirements -> Term -> Term -> Env -> Value
- VDelay :: Term -> Env -> Value
- VRef :: Int -> Value
- VIndir :: Int -> Value
- VRcd :: Map Var Value -> Value
- VKey :: KeyCombo -> Value
- VRequirements :: Text -> Term -> Env -> Value
- VSuspend :: Term -> Env -> Value
- VExc :: Value
- VBlackhole :: Value
- prettyValue :: Value -> Text
- valueToTerm :: Value -> Term
- data Env
- emptyEnv :: Env
- envTypes :: Lens' Env TCtx
- envReqs :: Lens' Env ReqCtx
- envVals :: Lens' Env VCtx
- envTydefs :: Lens' Env TDCtx
- lookupValue :: Var -> Env -> Maybe Value
- addBinding :: Var -> Typed Value -> Env -> Env
- addValueBinding :: Var -> Value -> Env -> Env
- addTydef :: Var -> TydefInfo -> Env -> Env
Values
A value is a term that cannot (or does not) take any more evaluation steps on its own.
VUnit :: Value | The unit value. |
VInt :: Integer -> Value | An integer. |
VText :: Text -> Value | Literal text. |
VDir :: Direction -> Value | A direction. |
VBool :: Bool -> Value | A boolean. |
VRobot :: Int -> Value | A reference to a robot. |
VInj :: Bool -> Value -> Value | An injection into a sum type. False = left, True = right. |
VPair :: Value -> Value -> Value | A pair. |
VClo :: Var -> Term -> Env -> Value | A closure, representing a lambda term along with an environment containing bindings for any free variables in the body of the lambda. |
VCApp :: Const -> [Value] -> Value | An application of a constant to some value arguments,
potentially waiting for more arguments. If a constant
application is fully saturated (as defined by its |
VBind :: Maybe Var -> Maybe Polytype -> Maybe Requirements -> Term -> Term -> Env -> Value | An unevaluated bind expression, waiting to be executed, of the
form i.e. |
VDelay :: Term -> Env -> Value | A (non-recursive) delayed term, along with its environment. If
a term would otherwise be evaluated but we don't want it to be
(e.g. as in the case of arguments to an 'if', or a recursive
binding), we can stick a |
VRef :: Int -> Value | A reference to a memory cell in the store. |
VIndir :: Int -> Value | An indirection to a value stored in a memory cell. The difference between VRef and VIndir is that VRef is a "real" value (of Ref type), whereas VIndir is just a placeholder. If a VRef is encountered during evaluation, it is the final result; if VIndir is encountered during evaluation, the value it points to should be looked up. |
VRcd :: Map Var Value -> Value | A record value. |
VKey :: KeyCombo -> Value | A keyboard input. |
VRequirements :: Text -> Term -> Env -> Value | A |
VSuspend :: Term -> Env -> Value | A |
VExc :: Value | A special value representing a program that terminated with an exception. |
VBlackhole :: Value | A special value used temporarily as the value for a variable
bound by a recursive let, while its definition is being
evaluated. If the variable is ever referenced again while its
value is still |
Instances
prettyValue :: Value -> Text Source #
Pretty-print a value.
valueToTerm :: Value -> Term Source #
Inject a value back into a term.
Environments
An environment is a record that stores relevant information for all the variables currently in scope.
Instances
FromJSON Env Source # | |
Defined in Swarm.Language.JSON | |
ToJSON Env Source # | |
Monoid Env Source # | |
Semigroup Env Source # | |
Generic Env Source # | |
Show Env Source # | |
Eq Env Source # | |
At Env Source # | |
Ixed Env Source # | |
Defined in Swarm.Language.Value | |
AsEmpty Env Source # | |
Defined in Swarm.Language.Value | |
type Rep Env Source # | |
Defined in Swarm.Language.Value | |
type Index Env Source # | |
Defined in Swarm.Language.Value | |
type IxValue Env Source # | |
Defined in Swarm.Language.Value |