-
-
Notifications
You must be signed in to change notification settings - Fork 9
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
- Loading branch information
1 parent
dba0c36
commit 891035b
Showing
2 changed files
with
48 additions
and
19 deletions.
There are no files selected for viewing
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
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -1,15 +1,33 @@ | ||
{-# LANGUAGE QuasiQuotes, OverloadedStrings #-} | ||
|
||
module ReplSpec (spec) where | ||
|
||
import Test.Hspec | ||
import Language.Mulang.Parsers.JavaScript | ||
import Language.Mulang.Interpreter.Repl | ||
import Language.Mulang.Interpreter.Internals (Value (..)) | ||
|
||
spec :: Spec | ||
spec = do | ||
describe "evalNext" $ do | ||
let session = newSession js | ||
describe "repl" $ do | ||
let s0 = newSession js | ||
it "evals and returns" $ do | ||
let (_, r1) = evalNext newSession "1" | ||
(r1, _) <- repl "1" s0 | ||
r1 `shouldBe` (MuNumber 1) | ||
|
||
it "can eval multiple statements and return" $ do | ||
(r1, s1) <- repl "var x = 1" s0 | ||
r1 `shouldBe` (MuNumber 1) | ||
|
||
(r2, s2) <- repl "x + 3" s1 | ||
r2 `shouldBe` (MuNumber 4) | ||
|
||
(_, s3) <- repl "function double(x) { return x * 2 }" s2 | ||
(r4, _) <- repl "double(x)" s3 | ||
r4 `shouldBe` (MuNumber 2) | ||
|
||
it "can save state" $ do | ||
(_, s1) <- repl "function succ(x) { return x + 1 }" s0 | ||
(_, s2) <- repl "function pred(x) { return x - 1 }" s1 | ||
|
||
(r, _) <- repl "succ(succ(pred(10)))" (reload s2) | ||
r `shouldBe` (MuNumber 11) | ||
|
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
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -1,37 +1,48 @@ | ||
module Language.Mulang.Interpreter.Repl ( | ||
Session (..), | ||
newSession, | ||
repl, | ||
newSession) where | ||
dump, | ||
load, | ||
reload) where | ||
|
||
import Data.Map ((!)) | ||
import Language.Mulang.Interpreter (Reference, ExecutionContext (..), globalObjects, defaultContext, eval) | ||
import Language.Mulang.Ast (Expression) | ||
import Language.Mulang.Interpreter (eval) | ||
import Language.Mulang.Interpreter.Internals (Value, Reference (..), ExecutionContext (..), defaultContext) | ||
|
||
import qualified Data.Map as Map | ||
import Data.Map ((!)) | ||
|
||
type SessionState = ([(Int, Value)], [Int]) | ||
type SessionLanguage = (String -> Expression) | ||
type Language = (String -> Expression) | ||
|
||
data Session = Session { language :: Language, context :: ExecutionContext } | ||
|
||
newSession :: Language -> Session | ||
newSession language = Session language defaultContext | ||
|
||
repl :: Session -> String -> IO (Session, Value) | ||
repl session line = do | ||
(ref, newContext) <- eval (context session) (language . session $ line) | ||
return (globalObjects newContext ! ref, newContext) | ||
repl :: String -> Session -> IO (Value, Session) | ||
repl line session = do | ||
(ref, newContext) <- eval (context session) (language session line) | ||
return (globalObjects newContext ! ref, session { context = newContext } ) | ||
|
||
dump :: Session -> SessionState | ||
dump (Session _ (ExecutationContext globals scopes _ _ _ )) = (dumpGlobals globals, dumpScopes scopes) | ||
dump (Session _ (ExecutionContext globals scopes _ _ _ )) = (dumpGlobals globals, dumpScopes scopes) | ||
where | ||
dumpGlobals = Map.toList . Map.mapKeys asInt | ||
dumpScopes = map asInt | ||
|
||
load :: SessionLanguage -> SessionState -> Session | ||
load language (globalsState, scopesState) = Session language (defaultContext { globalObjects = loadGlobals state, scopes = loadScopes state } ) | ||
load :: Language -> SessionState -> Session | ||
load language (globalsState, scopesState) = Session language (defaultContext { globalObjects = loadGlobals globalsState, scopes = loadScopes scopesState } ) | ||
where | ||
loadGlobals = Map.fromList . map fromInt | ||
loadGlobals = Map.mapKeys fromInt . Map.fromList | ||
loadScopes = map fromInt | ||
|
||
reload :: Session -> Session | ||
reload s@(Session l _) = load l (dump s) | ||
|
||
fromInt :: Int -> Reference | ||
fromInt = Reference | ||
|
||
toInt :: Reference -> Int | ||
toInt (Reference i) = i | ||
asInt :: Reference -> Int | ||
asInt (Reference i) = i |