Skip to content

Commit

Permalink
Replace Token lists with Vectors for the Scanner & Parser
Browse files Browse the repository at this point in the history
  • Loading branch information
0rphee committed Jan 6, 2025
1 parent 289b308 commit 68859a9
Show file tree
Hide file tree
Showing 4 changed files with 28 additions and 14 deletions.
2 changes: 1 addition & 1 deletion src/Interpreter.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ import Stmt qualified
import TokenType qualified

{-# SPECIALIZE whileM ::

Check warning on line 34 in src/Interpreter.hs

View workflow job for this annotation

GitHub Actions / 9.10.1 on ubuntu-latest

Orphan rule: "USPEC whileM @(ExceptT

Check warning on line 34 in src/Interpreter.hs

View workflow job for this annotation

GitHub Actions / 9.6.5 on macos-latest

Orphan rule: "USPEC whileM @(ExceptT

Check warning on line 34 in src/Interpreter.hs

View workflow job for this annotation

GitHub Actions / 9.6.5 on ubuntu-latest

Orphan rule: "USPEC whileM @(ExceptT
InterpreterM Bool -> InterpreterM Bool -> InterpreterM ()
InterpreterM Bool -> InterpreterM a -> InterpreterM ()
#-}

evaluate :: Expr.Expr -> InterpreterM Expr.LiteralValue
Expand Down
9 changes: 5 additions & 4 deletions src/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ import VectorBuilder.Vector qualified as VB

data Parser = Parser
{ current :: !Int
, tokens :: ![Token]
, tokens :: !(Vector Token)
}
deriving (Show)

Expand All @@ -39,7 +39,7 @@ type ParserM r a =

data ParseException = ParseException

runParse :: [Token] -> IO (Maybe (Vector Stmt.Stmt), Error.ErrorPresent)
runParse :: Vector Token -> IO (Maybe (Vector Stmt.Stmt), Error.ErrorPresent)
runParse tokens = do
(r, w) <- (evalRWST . runExceptT) parse () initialParserState
pure (either (const Nothing) Just r, w)
Expand Down Expand Up @@ -393,8 +393,9 @@ advance = do
isAtEnd :: ParserM r Bool
isAtEnd = (\t -> t.ttype == EOF) <$> peek

-- TODO: unsafeIndex ?
peek :: ParserM r Token
peek = get <&> \pr -> pr.tokens !! pr.current
peek = get <&> \pr -> pr.tokens V.! pr.current

previous :: ParserM r Token
previous = get <&> \pr -> pr.tokens !! (pr.current - 1)
previous = get <&> \pr -> pr.tokens V.! (pr.current - 1)
19 changes: 11 additions & 8 deletions src/Scanner.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,17 +10,19 @@ import Data.ByteString.Char8 (ByteString)
import Data.ByteString.Char8 qualified as BS
import Data.Char (isAlpha, isDigit)
import Data.Functor ((<&>))
import Data.Vector (Vector)
import Error qualified
import TokenType (Token (..), TokenType (..))
import VectorBuilder.Builder as VB
import VectorBuilder.Vector as VB

data Scanner = Scanner
{ source :: !ByteString
, tokens :: ![Token]
, tokens :: !(VB.Builder Token)
, start :: !Int
, current :: !Int
, line :: !Int
}
deriving (Show)

type ScanM r a = RWST r Error.ErrorPresent Scanner IO a

Expand All @@ -33,7 +35,7 @@ myIsAlpha c = isAlpha c || c == '_'
myIsAlphaNum :: Char -> Bool
myIsAlphaNum c = myIsAlpha c || isDigit c

scanTokens :: ByteString -> IO ([Token], Error.ErrorPresent)
scanTokens :: ByteString -> IO (Vector Token, Error.ErrorPresent)
scanTokens source = (\act -> evalRWST act () initialScanner) $ do
whileM
(not <$> isAtEnd)
Expand All @@ -44,16 +46,17 @@ scanTokens source = (\act -> evalRWST act () initialScanner) $ do
modify' $ \sc ->
sc
{ tokens =
Token {ttype = EOF, lexeme = "", tline = sc.line}
: sc.tokens
sc.tokens
<> VB.singleton
(Token {ttype = EOF, lexeme = "", tline = sc.line})
}

get <&> (reverse . (.tokens))
get <&> (VB.build . (.tokens))
where
initialScanner =
Scanner
{ source = source
, tokens = []
, tokens = VB.empty
, start = 0
, current = 0
, line = 1
Expand Down Expand Up @@ -120,7 +123,7 @@ scanTokens source = (\act -> evalRWST act () initialScanner) $ do
addToken2 ttype = modify' $ \sc ->
-- substring
let text = substring sc.source sc.start sc.current
in sc {tokens = Token ttype text sc.line : sc.tokens}
in sc {tokens = sc.tokens <> VB.singleton (Token ttype text sc.line)}
match :: forall r. Char -> ScanM r Bool
match expected = do
e <- isAtEnd
Expand Down
12 changes: 11 additions & 1 deletion test/ch10.lox
Original file line number Diff line number Diff line change
@@ -1,10 +1,12 @@
var t1 = clock();

fun fib(n) {
if (n <= 1) return n;
return fib(n - 2) + fib(n - 1);
}

print "begin fib";
for (var i = 0; i < 20; i = i + 1) {
for (var i = 0; i < 35; i = i + 1) {
print fib(i);
}
print "end fib, begin count";
Expand Down Expand Up @@ -38,3 +40,11 @@ var a = "global";
var a = "block";
showA(); // and this prints "block"
}

var t2 = clock();

print "";

print "time diff";

print t2 - t1;

0 comments on commit 68859a9

Please sign in to comment.