Skip to content

Commit

Permalink
Scanner: convert strings and numbers to their runtime values
Browse files Browse the repository at this point in the history
this adds 'Object' and replaces 'Maybe String' with 'Maybe Object' for
the literal in 'Token'
  • Loading branch information
ccntrq committed Jan 6, 2018
1 parent d3d38bc commit 3342970
Show file tree
Hide file tree
Showing 3 changed files with 13 additions and 7 deletions.
3 changes: 3 additions & 0 deletions src/Object.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
module Object where

data Object = Number Double | String String deriving (Show)
14 changes: 8 additions & 6 deletions src/Scanner.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ import Util

import Token
import TokenType
import Object

import Control.Conditional

Expand Down Expand Up @@ -106,8 +107,6 @@ identifier = (munchChars isAlphaNumeric) >> do
Just t -> addToken t
Nothing -> addToken IDENTIFIER

-- TODO:
-- * create runtime value
number :: Scanner Token
number = (munchChars isDigit) >> do
c <- peek
Expand All @@ -116,9 +115,6 @@ number = (munchChars isDigit) >> do
then advance >> munchChars isDigit >> addToken NUMBER
else addToken NUMBER

-- TODO:
-- * strip the quotes
-- * create runtime value
string :: Scanner Token
string = scanString >> ifM (isAtEnd) (unterminatedString) (advance >> addToken STRING)
where
Expand Down Expand Up @@ -153,9 +149,15 @@ addToken :: TokenType -> Scanner Token
addToken t = do
st <- get
let lexeme = slice (start st) (current st) (source st)
let token = Token t lexeme Nothing (line st)
let literal = literalFromLexeme t lexeme
let token = Token t lexeme literal (line st)
put (st {tokens = token : (tokens st)})
return token
where
literalFromLexeme :: TokenType -> String -> Maybe Object
literalFromLexeme NUMBER l = Just $ Number (read l)
literalFromLexeme STRING l = Just $ String ((init . tail) l) -- trim the qoutes
literalFromLexeme _ _ = Nothing

isAtEnd :: Scanner Bool
isAtEnd = do
Expand Down
3 changes: 2 additions & 1 deletion src/Token.hs
Original file line number Diff line number Diff line change
@@ -1,10 +1,11 @@
module Token where

import TokenType
import Object

data Token = Token
{ t_type :: TokenType
, t_lexeme :: String
, t_literal :: Maybe String -- TODO: Convert to runtime value
, t_literal :: Maybe Object
, t_line :: Int
} deriving (Show)

0 comments on commit 3342970

Please sign in to comment.