Last active
August 29, 2015 14:12
-
-
Save actsasbuffoon/6c823ed6fa14bc2d0616 to your computer and use it in GitHub Desktop.
The beginnings of a simple imperative language in Haskell
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE ViewPatterns #-} | |
{-# OPTIONS_GHC -Wall #-} | |
module Main where | |
-- This is a simple dynamically typed imperative language with mutable state. It's somewhat similar to JavaScript, but | |
-- it differs in many ways. There are a few notable oddities to the language that I'm still working out. For instance, | |
-- we don't have reference types. In most languages you would write something like this: | |
-- | |
-- foo = new Person("Mike") | |
-- bar = foo | |
-- foo.first_name = "Michael" | |
-- foo.first_name | |
-- # => "Michael" | |
-- bar.first_name | |
-- # => "Michael" | |
-- | |
-- Since this language doesn't yet have reference types, you'd end up with this surprising result: | |
-- | |
-- foo = new Person("Mike") | |
-- bar = foo | |
-- foo.first_name = "Michael" | |
-- foo.first_name | |
-- # => "Michael" | |
-- bar.first_name | |
-- # => "Mike" | |
-- | |
-- Additionally, while functions get their own local scope, it's based on the scope they're being called | |
-- from, not the scope where they were defined. I'm working on fixing that as well, but it runs into the | |
-- same problems with immutability that make reference types a bit challenging. | |
import qualified Data.Map as M | |
import Control.Monad.State.Strict | |
import Data.Maybe | |
import qualified Data.Sequence as S | |
import Data.List (intercalate, findIndex) | |
import Data.Foldable (toList) | |
import Control.Applicative | |
-- These are the basic data types so far. | |
data Object = OBool Bool | |
| ONil | |
| OInt Int | |
| OArray (S.Seq Object) | |
-- [String] represents the argument names, while `Action` is the bodyof the function. | |
| OFunc [String] Action | |
-- These haven't really been fleshed out yet. | |
| OClass { | |
className :: String, | |
parentClass :: Object, | |
classProperties :: Object, | |
instanceProperties :: Object | |
} | |
-- These also aren't really working yet. | |
| OObj { | |
oClass :: Object, | |
instanceState :: M.Map String Object | |
} | |
-- Not an elegant FFI, but it works. | |
| NativeFunc ([Object] -> Object) | |
instance Show Object where | |
show (OBool True) = "true" | |
show (OBool False) = "false" | |
show ONil = "nil" | |
show (OInt x) = show x | |
show (OArray s) = "[" ++ intercalate ", " (toList $ fmap show s) ++ "]" | |
show (OFunc args body) = "func(" ++ intercalate ", " args ++ ") { " ++ show body ++ " }" | |
show (OClass name _ _ _) = name | |
show (OObj cls _) = "<" ++ show cls ++ ">" | |
show (NativeFunc _) = "[NativeFunction]" | |
-- These represent a scope for variables. There's a global one, and functions get their own local scope. | |
-- The `objects` Seq is like a local heap. It isn't really being used yet. It's a stub for a later idea. | |
data Scope = Scope { | |
bindings :: M.Map String Object, | |
objects :: S.Seq Object | |
} | |
instance Show Scope where | |
show world = showMap $ bindings world | |
-- These are part of my (in progress) plan to implement reference types. Haskell has no concept of reference types, | |
-- because everything is immutable. This language has mutable state, so we'll need reference types. | |
-- The idea is that reference type objects will go into a heap, and a reference will point to an offset | |
-- in that heap. Instead of variables pointint directly at objects, they will point at references. That | |
-- means we can create a new `Scope` (with a different object at a given index), and now references will | |
-- look at their index in the new heap, and we've got something that looks like reference types. | |
data Reference = Reference { | |
refContext :: Scope, | |
refIndex :: Int | |
} | |
-- These are the kinds of things you can do in the language. | |
data Action = Assign String Action -- Bind a value to a name | |
| Lookup String -- Lookup a value in the current scope | |
| If Action Action Action -- If statements with an else. Else-if can be implemented by putting nested `If`s on the else-side. | |
| Value Object -- Fully reduced values. Things like OInt, OBool, etc. | |
| RefVal Reference | |
| AndThen Action Action -- This is how multiple expressions are chained together. | |
| BinOper BinOp Action Action -- Binary operations (+, &&, ||, etc.) | |
| IBinOper IBinOp Action Action -- In-place binary operations (+=, *=, etc.) | |
| IUnaryOper IUnaryOp Action -- In-place unary operations (++, --, etc.) | |
| ArrayView Action Action -- Indexing into an array | |
| NativeCall Object [Action] -- Calling a native Haskell function | |
| FuncDef String [String] Action -- A named function (anonymous functions are just a kind of `Value`). | |
| FuncCall Action [Action] -- Calling a function with arguments | |
| WithScope Scope Action -- Introducing a new scope (for functions) | |
data BinOp = Add | |
| Subtract | |
| Multiply | |
| Divide | |
| GreaterThan | |
| LessThan | |
| And | |
| Or | |
data IBinOp = IAdd | |
| ISubtract | |
| IMultiply | |
| IDivide | |
data IUnaryOp = Increment | |
| Decrement | |
-- For printing out the contents of Scopes | |
showMap :: (Show a, Show b) => M.Map a b -> String | |
showMap m = "{" ++ intercalate ", " ((\(k, v) -> show k ++ ": " ++ show v) <$> M.toList m) ++ "}" | |
instance Show Action where | |
show (Assign name value) = name ++ " = " ++ show value | |
show (Lookup name) = name | |
show (If cond left right) = "if (" ++ show cond ++ ") { " ++ show left ++ " } else { " ++ show right ++ " }" | |
show (Value v) = show v | |
show (AndThen left right) = show left ++ "; \n" ++ show right | |
show (BinOper GreaterThan left right) = show left ++ " > " ++ show right | |
show (BinOper LessThan left right) = show left ++ " < " ++ show right | |
show (BinOper Add left right) = show left ++ " + " ++ show right | |
show (BinOper Subtract left right) = show left ++ " - " ++ show right | |
show (BinOper Multiply left right) = show left ++ " * " ++ show right | |
show (BinOper Divide left right) = show left ++ " / " ++ show right | |
show (BinOper And left right) = show left ++ " && " ++ show right | |
show (BinOper Or left right) = show left ++ " || " ++ show right | |
show (IUnaryOper Increment val) = show val ++ "++" | |
show (IUnaryOper Decrement val) = show val ++ "--" | |
show (IBinOper IAdd left right) = show left ++ " += " ++ show right | |
show (IBinOper ISubtract left right) = show left ++ " -= " ++ show right | |
show (IBinOper IMultiply left right) = show left ++ " *= " ++ show right | |
show (IBinOper IDivide left right) = show left ++ " /= " ++ show right | |
show (ArrayView ary idx) = show ary ++ "[" ++ show idx ++ "]" | |
show (NativeCall _ _) = "[NativeCall]" | |
show (RefVal (Reference _ i)) = "[Reference#" ++ show i ++ "]" | |
show (FuncDef name args body) = "def " ++ name ++ "(" ++ intercalate ", " args ++ ") { " ++ show body ++ " }" | |
show (FuncCall fn args) = show fn ++ "(" ++ intercalate ", " (fmap show args) ++ ")" | |
show (WithScope w body) = "<local scope " ++ show w ++ "> {\n" ++ show body ++ "\n}" | |
-- Part of my not-quite-working plan for reference types. | |
createObj :: Object -> State Scope Reference | |
createObj val = do | |
w <- get | |
let idx = S.length $ objects w | |
let n = w { objects = objects w S.|> val } | |
put n | |
return $ Reference n idx | |
-- Value actions are fully reduced, everything else can be reduced further. | |
reducible :: Action -> Bool | |
reducible (Value _) = False | |
reducible _ = True | |
-- Just a shortcut to make the view patterns more terse. | |
anyReducible :: [Action] -> Bool | |
anyReducible = any reducible | |
-- Reduce the first reducible Action in a list. Mostly used for arguments. | |
reduceFirst :: [Action] -> State Scope [Action] | |
reduceFirst xs = do | |
let i = fromMaybe (error "Could not find argument") $ findIndex reducible xs | |
evaluated <- reduce $ xs !! i | |
return $ take i xs ++ [evaluated] ++ drop (i + 1) xs | |
-- False and Nil are falsey, everything else is truthy. | |
isTruthy :: Action -> Bool | |
isTruthy (Value (OBool False)) = False | |
isTruthy (Value ONil) = False | |
isTruthy (Value _) = True | |
isTruthy _ = error "Only values can be checked for truthiness. Did you forget to reduce something?" | |
-- Shortcut for printing out type errors for binary operators | |
twoOpErr :: String -> String -> a | |
twoOpErr op ty = error $ op ++ ": Left and right operands must both be " ++ ty | |
-- Shortcut for printing out type errors for unary operators | |
oneOpErr :: String -> String -> a | |
oneOpErr op ty = error $ op ++ ": Operand must be " ++ ty | |
-- Run a binary operator. | |
runBinOp :: BinOp -> Object -> Object -> Object | |
runBinOp Add (OInt left) (OInt right) = OInt $ left + right | |
runBinOp Add _ _ = twoOpErr "+" "integers" | |
runBinOp Subtract (OInt left) (OInt right) = OInt $ left - right | |
runBinOp Subtract _ _ = twoOpErr "-" "integers" | |
runBinOp Multiply (OInt left) (OInt right) = OInt $ left * right | |
runBinOp Multiply _ _ = twoOpErr "*" "integers" | |
runBinOp Divide (OInt left) (OInt right) = OInt $ left `div` right | |
runBinOp Divide _ _ = twoOpErr "/" "integers" | |
runBinOp GreaterThan (OInt left) (OInt right) = OBool $ left > right | |
runBinOp GreaterThan _ _ = twoOpErr ">" "integers" | |
runBinOp LessThan (OInt left) (OInt right) = OBool $ left < right | |
runBinOp LessThan _ _ = twoOpErr "<" "integers" | |
runBinOp And (OBool left) (OBool right) = OBool $ left && right | |
runBinOp And _ _ = twoOpErr "&&" "booleans" | |
runBinOp Or (OBool left) (OBool right) = OBool $ left || right | |
runBinOp Or _ _ = twoOpErr "||" "booleans" | |
-- Run an in-place unary operator | |
runIUnaryOp :: IUnaryOp -> Object -> Object | |
runIUnaryOp Increment (OInt val) = OInt $ val + 1 | |
runIUnaryOp Increment _ = oneOpErr "++" "integer" | |
runIUnaryOp Decrement (OInt val) = OInt $ val - 1 | |
runIUnaryOp Decrement _ = oneOpErr "--" "integer" | |
-- Run an in-place binary operator | |
runIBinOp :: IBinOp -> Object -> Object -> Object | |
runIBinOp IAdd (OInt left) (OInt right) = OInt $ left + right | |
runIBinOp IAdd _ _ = twoOpErr "+=" "integers" | |
runIBinOp ISubtract (OInt left) (OInt right) = OInt $ left - right | |
runIBinOp ISubtract _ _ = twoOpErr "-=" "integers" | |
runIBinOp IMultiply (OInt left) (OInt right) = OInt $ left * right | |
runIBinOp IMultiply _ _ = twoOpErr "*=" "integers" | |
runIBinOp IDivide (OInt left) (OInt right) = OInt $ left `div` right | |
runIBinOp IDivide _ _ = twoOpErr "/=" "integers" | |
-- Unwrap a list of Values into a list of Objects | |
fromValues :: [Action] -> [Object] | |
fromValues = fmap fromValue | |
-- A Value wraps an Object. This extracts the Object. | |
fromValue :: Action -> Object | |
fromValue (Value x) = x | |
fromValue _ = error "Cannot get value from non-Value" | |
reduce :: Action -> State Scope Action | |
-- Here's where the important stuff lives. `reduce` performs a single step. Usually it checks to see | |
-- if the arguments are fully reduced. If not, it returns a duplicate of the Action with a reduced | |
-- argument. Once everything is reduced, it performs its operation. | |
reduce (NativeCall fn args@(anyReducible -> True)) = do | |
evaluated <- reduceFirst args | |
return $ NativeCall fn evaluated | |
reduce (NativeCall (NativeFunc fn) args) = return $ Value $ fn $ fromValues args | |
reduce (NativeCall _ _) = error "Something went wrong when reducing a NativeCall" | |
reduce (IBinOper op name value@(reducible -> True)) = do | |
evaluated <- reduce value | |
return $ IBinOper op name evaluated | |
-- These in-place operators work in a weird way. I need the name of the binding to modify. I get it | |
-- by not fully reducing a Lookup, and extracting its name. I reallly don't like this approach, but | |
-- I'm not sure how to make it better. | |
reduce (IBinOper op (Lookup name) (Value value)) = do | |
w <- get | |
let old = M.lookup name $ bindings w | |
let modified = runIBinOp op (fromMaybe (error "cannot modify non-existent value") old) value | |
put $ w { bindings = M.insert name modified (bindings w) } | |
return $ Value modified | |
reduce IBinOper{} = error "Unsupported type of in-place binary operation" | |
reduce (IUnaryOper op (Lookup name)) = do | |
w <- get | |
let old = M.lookup name (bindings w) | |
let modified = runIUnaryOp op (fromMaybe (error "Cannot modify non-existent value") old) | |
put $ w { bindings = M.insert name modified (bindings w) } | |
return $ Value modified | |
reduce IUnaryOper{} = error "Unsupported type of unary operation" | |
reduce (BinOper op left@(reducible -> True) right) = do | |
evaluated <- reduce left | |
return $ BinOper op evaluated right | |
reduce (BinOper op left right@(reducible -> True)) = do | |
evaluated <- reduce right | |
return $ BinOper op left evaluated | |
reduce (BinOper op (Value left) (Value right)) = return $ Value $ runBinOp op left right | |
reduce BinOper{} = error "This shouldn't happen" | |
reduce (Assign name value@(reducible -> True)) = do | |
evaluated <- reduce value | |
return $ Assign name evaluated | |
reduce (Assign name (Value value)) = do | |
w <- get | |
let newScope = M.insert name value $ bindings w | |
put $ w { bindings = newScope} | |
return $ Value value | |
reduce (Assign _ _) = error "This shouldn't happen" | |
reduce (Lookup name) = do | |
w <- get | |
let m = M.lookup name (bindings w) | |
return $ Value $ fromMaybe ONil m | |
reduce (Value o) = return $ Value o | |
reduce (RefVal r) = return $ RefVal r | |
reduce (If cond@(reducible -> True) whenTrue whenFalse) = do | |
evaluated <- reduce cond | |
return $ If evaluated whenTrue whenFalse | |
reduce (If (isTruthy -> True) whenTrue _) = return whenTrue | |
reduce (If (isTruthy -> False) _ whenFalse) = return whenFalse | |
reduce If{} = error "You somehow ended up with a non-reducible IF condition that isn't truthy or falsey. Weird." | |
reduce (AndThen left@(reducible -> True) right) = do | |
evaluated <- reduce left | |
return $ AndThen evaluated right | |
reduce (AndThen _ right) = return right | |
reduce (ArrayView ary@(reducible -> True) idx) = do | |
evaluated <- reduce ary | |
return $ ArrayView evaluated idx | |
reduce (ArrayView ary idx@(reducible -> True)) = do | |
evaluated <- reduce idx | |
return $ ArrayView ary evaluated | |
reduce (ArrayView (Value (OArray ary)) (Value (OInt idx))) = return $ Value $ S.index ary idx | |
reduce ArrayView{} = error "Can only do array access on arrays with integers" | |
reduce (FuncDef name args body) = return $ Assign name $ Value $ OFunc args body | |
reduce (FuncCall fn@(reducible -> True) args) = do | |
evaluated <- reduce fn | |
return $ FuncCall evaluated args | |
reduce (FuncCall fn args@(anyReducible -> True)) = do | |
evaluated <- reduceFirst args | |
return $ FuncCall fn evaluated | |
reduce (FuncCall (Value (OFunc fargs body)) args) = do | |
let args' = zip fargs args | |
currentScope <- get | |
return $ WithScope currentScope (AndThen (makeBindings args') body) | |
-- If FuncCall has a NativeFunc (rather than a regular OFunc), then it returns a NativeCall. This way the | |
-- parser won't need to know which functions are native and which are regular. | |
reduce (FuncCall (Value fn@(NativeFunc _)) args) = return $ NativeCall fn args | |
reduce (FuncCall _ _) = error "Tried to call a function strangely" | |
-- Reducing a WithScope involves using a nested State monad. This allows us to leave our parent | |
-- Scope alone. | |
reduce (WithScope world body@(reducible -> True)) = do | |
let (evaluated, scope) = runState (reduce body) world | |
return $ WithScope scope evaluated | |
reduce (WithScope _ body) = return body | |
-- This takes a list of variable names, and a list of values. It creates a series of `AndThen` actions | |
-- with Assign nodes in them. This is how we bind arguments inside of functions. | |
makeBindings :: [(String, Action)] -> Action | |
makeBindings [] = Value ONil | |
makeBindings ((name, obj):xs) = AndThen (Assign name obj) (makeBindings xs) | |
runProg :: Action -> Scope -> IO () | |
runProg a w = do | |
let (a', w') = runState (reduce a) w | |
putStrLn $ "\nGlobal Scope: " ++ show w' ++ "\n" | |
print a' | |
when (reducible a') $ runProg a' w' | |
-- An example foreign function | |
isONil' :: Object -> Bool | |
isONil' ONil = True | |
isONil' _ = False | |
isONil :: [Object] -> Object | |
isONil (x:_) = OBool $ isONil' x | |
isONil _ = OBool True | |
-- The starting global scope, pre-populated with our foreign function. | |
initScope :: Scope | |
initScope = Scope (M.fromList [("is_nil?", NativeFunc isONil)]) empty | |
main :: IO () | |
main = do | |
print prog | |
runProg prog initScope | |
where | |
prog = AndThen | |
(FuncDef "try" ["x", "fn"] | |
(If (FuncCall (Lookup "is_nil?") [(Lookup "x")]) | |
(Value ONil) | |
(FuncCall (Lookup "fn") [(Lookup "x")]))) | |
(AndThen | |
(FuncDef "add2" ["a"] | |
(BinOper Add (Lookup "a") (Value $ OInt 2))) | |
(FuncCall (Lookup "try") [Value $ OInt 3, Lookup "add2"])) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
def try(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }; | |
def add2(a) { a + 2 }; | |
try(3, add2) | |
Global Scope: {"is_nil?": [NativeFunction]} | |
try = func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }; | |
def add2(a) { a + 2 }; | |
try(3, add2) | |
Global Scope: {"is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }; | |
def add2(a) { a + 2 }; | |
try(3, add2) | |
Global Scope: {"is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
def add2(a) { a + 2 }; | |
try(3, add2) | |
Global Scope: {"is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
add2 = func(a) { a + 2 }; | |
try(3, add2) | |
Global Scope: {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
func(a) { a + 2 }; | |
try(3, add2) | |
Global Scope: {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
try(3, add2) | |
Global Scope: {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }(3, add2) | |
Global Scope: {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }(3, func(a) { a + 2 }) | |
Global Scope: {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
<local scope {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }}> { | |
x = 3; | |
fn = func(a) { a + 2 }; | |
nil; | |
if (is_nil?(x)) { nil } else { fn(x) } | |
} | |
Global Scope: {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
<local scope {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }, "x": 3}> { | |
3; | |
fn = func(a) { a + 2 }; | |
nil; | |
if (is_nil?(x)) { nil } else { fn(x) } | |
} | |
Global Scope: {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
<local scope {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }, "x": 3}> { | |
fn = func(a) { a + 2 }; | |
nil; | |
if (is_nil?(x)) { nil } else { fn(x) } | |
} | |
Global Scope: {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
<local scope {"add2": func(a) { a + 2 }, "fn": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }, "x": 3}> { | |
func(a) { a + 2 }; | |
nil; | |
if (is_nil?(x)) { nil } else { fn(x) } | |
} | |
Global Scope: {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
<local scope {"add2": func(a) { a + 2 }, "fn": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }, "x": 3}> { | |
nil; | |
if (is_nil?(x)) { nil } else { fn(x) } | |
} | |
Global Scope: {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
<local scope {"add2": func(a) { a + 2 }, "fn": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }, "x": 3}> { | |
if (is_nil?(x)) { nil } else { fn(x) } | |
} | |
Global Scope: {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
<local scope {"add2": func(a) { a + 2 }, "fn": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }, "x": 3}> { | |
if ([NativeFunction](x)) { nil } else { fn(x) } | |
} | |
Global Scope: {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
<local scope {"add2": func(a) { a + 2 }, "fn": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }, "x": 3}> { | |
if ([NativeFunction](3)) { nil } else { fn(x) } | |
} | |
Global Scope: {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
<local scope {"add2": func(a) { a + 2 }, "fn": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }, "x": 3}> { | |
if ([NativeCall]) { nil } else { fn(x) } | |
} | |
Global Scope: {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
<local scope {"add2": func(a) { a + 2 }, "fn": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }, "x": 3}> { | |
if (false) { nil } else { fn(x) } | |
} | |
Global Scope: {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
<local scope {"add2": func(a) { a + 2 }, "fn": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }, "x": 3}> { | |
fn(x) | |
} | |
Global Scope: {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
<local scope {"add2": func(a) { a + 2 }, "fn": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }, "x": 3}> { | |
func(a) { a + 2 }(x) | |
} | |
Global Scope: {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
<local scope {"add2": func(a) { a + 2 }, "fn": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }, "x": 3}> { | |
func(a) { a + 2 }(3) | |
} | |
Global Scope: {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
<local scope {"add2": func(a) { a + 2 }, "fn": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }, "x": 3}> { | |
<local scope {"add2": func(a) { a + 2 }, "fn": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }, "x": 3}> { | |
a = 3; | |
nil; | |
a + 2 | |
} | |
} | |
Global Scope: {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
<local scope {"add2": func(a) { a + 2 }, "fn": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }, "x": 3}> { | |
<local scope {"a": 3, "add2": func(a) { a + 2 }, "fn": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }, "x": 3}> { | |
3; | |
nil; | |
a + 2 | |
} | |
} | |
Global Scope: {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
<local scope {"add2": func(a) { a + 2 }, "fn": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }, "x": 3}> { | |
<local scope {"a": 3, "add2": func(a) { a + 2 }, "fn": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }, "x": 3}> { | |
nil; | |
a + 2 | |
} | |
} | |
Global Scope: {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
<local scope {"add2": func(a) { a + 2 }, "fn": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }, "x": 3}> { | |
<local scope {"a": 3, "add2": func(a) { a + 2 }, "fn": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }, "x": 3}> { | |
a + 2 | |
} | |
} | |
Global Scope: {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
<local scope {"add2": func(a) { a + 2 }, "fn": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }, "x": 3}> { | |
<local scope {"a": 3, "add2": func(a) { a + 2 }, "fn": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }, "x": 3}> { | |
3 + 2 | |
} | |
} | |
Global Scope: {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
<local scope {"add2": func(a) { a + 2 }, "fn": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }, "x": 3}> { | |
<local scope {"a": 3, "add2": func(a) { a + 2 }, "fn": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }, "x": 3}> { | |
5 | |
} | |
} | |
Global Scope: {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
<local scope {"add2": func(a) { a + 2 }, "fn": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }, "x": 3}> { | |
5 | |
} | |
Global Scope: {"add2": func(a) { a + 2 }, "is_nil?": [NativeFunction], "try": func(x, fn) { if (is_nil?(x)) { nil } else { fn(x) } }} | |
5 |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment