Skip to content

Commit

Permalink
All tests pass now!
Browse files Browse the repository at this point in the history
  • Loading branch information
0rphee committed Jan 12, 2025
1 parent 24dc862 commit a8086cd
Show file tree
Hide file tree
Showing 3 changed files with 13 additions and 48 deletions.
9 changes: 8 additions & 1 deletion README.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,10 @@
# xolsh - hslox

A work-in-progress Haskell implementation of the `lox` programming language (jlox) from the [Crafting Interpreters Book](https://craftinginterpreters.com/).
A complete Haskell tree-walking implementation of the `lox` programming language (jlox) from the [Crafting Interpreters Book](https://craftinginterpreters.com/). It fully passes the jlox test suite.

The code style of the interpreter is mostly a port/adaptation of the original java implementation, with a more idiomatic Haskell style where possible.

- Areas for improvement:
- Try to write a one-pass scanning-parsing step with parser combinators (w/flatparse) to compare performance.
- Optimize variable & field access (through vectors?).
- A rewrite with an effect system would probably give many benefits, specially to the code style.
47 changes: 1 addition & 46 deletions src/Environment.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedRecordDot #-}

module Environment
Expand Down Expand Up @@ -47,10 +46,7 @@ data Environment
{ values :: IORef (Map ByteString Expr.LiteralValue)
, _enclosing :: Environment
}
deriving (Show, Eq)

instance Show (IORef (Map ByteString Expr.LiteralValue)) where
show _ = "iorefmap"
deriving (Eq)

lookUpVariable :: TokenType.Token -> Int -> InterpreterM Expr.LiteralValue
lookUpVariable name distance =
Expand Down Expand Up @@ -126,45 +122,4 @@ define
define name value environment = do
liftIO $ modifyIORef' environment.values $ \valueMap -> M.insert name value valueMap

{-# INLINEABLE get #-}
get :: TokenType.Token -> InterpreterM Expr.LiteralValue
get name = do
state <- State.get
envget state.environment >>= \case
Just v -> pure v
Nothing ->
throwError $
Error.RuntimeError name ("Undefined variable '" <> name.lexeme <> "'.")
where
envget :: Environment -> InterpreterM (Maybe Expr.LiteralValue)
envget env =
liftIO (readIORef env.values) >>= \valueMap ->
case valueMap M.!? name.lexeme of
Nothing ->
case env of
LocalEnvironment _ enc -> envget enc
_ -> pure Nothing
v -> pure v

{-# INLINEABLE assign #-}
assign :: TokenType.Token -> Expr.LiteralValue -> InterpreterM ()
assign name value = do
-- there's no implicit variable declaration like in python
state <- State.get
envassign state.environment >>= \case
True -> pure ()
False ->
throwError $
Error.RuntimeError name ("Undefined variable '" <> name.lexeme <> "'.")
where
-- True if successful assignment, False otherwise
envassign :: Environment -> InterpreterM Bool
envassign env = do
liftIO (readIORef env.values) >>= \vals ->
if M.member name.lexeme vals
then define name.lexeme value env >> pure True
else case env of
GlobalEnvironment _ -> pure False
LocalEnvironment _ enclosing -> envassign enclosing

----------------------------------
5 changes: 4 additions & 1 deletion src/Interpreter.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ import Data.Vector qualified as V
import Environment
import Error qualified
import Expr qualified
import Numeric qualified
import Scanner (whileM)
import Stmt qualified
import TokenType qualified
Expand Down Expand Up @@ -209,8 +210,10 @@ stringify :: Expr.LiteralValue -> InterpreterM ByteString
stringify = \case
Expr.LNil -> pure "nil"
Expr.LNumber v ->
-- see https://docs.oracle.com/javase/8/docs/api/java/lang/Double.html#toString-double-
-- not exactly the same as jlox due to Double.toString() semantics, but this satisfies the jlox tests
pure $
let str = BS.pack $ show v
let str = BS.pack $ Numeric.showFFloat Nothing v ""
(pstr, end) = BS.splitAt (BS.length str - 2) str
in if end == ".0"
then pstr
Expand Down

0 comments on commit a8086cd

Please sign in to comment.