added boolean type
This commit is contained in:
@@ -5,6 +5,7 @@ import BC.Types
|
||||
eval :: [Value] -> Value
|
||||
eval [x@(BInt _)] = x
|
||||
eval [x@(BFloat _)] = x
|
||||
eval [x@(BBool _)] = x
|
||||
eval [x@(BErr _)] = x
|
||||
eval [(BOp x)] = BErr ("operation " ++ x ++ " requires arguments")
|
||||
eval [] = BOp ""
|
||||
@@ -15,6 +16,8 @@ treeEval [] [] (num:_) = num
|
||||
treeEval [] ops nums = handleOp [] ops nums
|
||||
treeEval (x@(BInt _):xy) ops nums = treeEval xy ops (x:nums)
|
||||
treeEval (x@(BFloat _):xy) ops nums = treeEval xy ops (x:nums)
|
||||
treeEval ((BBool x):xy) ops nums =
|
||||
treeEval xy ops ((BInt $ if x then 1 else 0):nums)
|
||||
treeEval expr@(x@(BOp _):xy) ops@(op:_) nums =
|
||||
if precedence x > precedence op
|
||||
then treeEval xy (x:ops) nums
|
||||
|
@@ -33,13 +33,29 @@ integer = do
|
||||
Just "-" -> (return . BInt . read) ("-" ++ x)
|
||||
_ -> (return . BInt . read) x
|
||||
|
||||
|
||||
bool :: P.Parser Value
|
||||
bool = P.try parseTrue P.<|> parseFalse
|
||||
where parseTrue = do
|
||||
_ <- P.string "true"
|
||||
return $ BBool True
|
||||
parseFalse = do
|
||||
_ <- P.string "false"
|
||||
return $ BBool False
|
||||
|
||||
|
||||
operator :: P.Parser Value
|
||||
operator = do
|
||||
res <- P.many1 $ P.letter P.<|> symbol
|
||||
return $ BOp res
|
||||
|
||||
|
||||
types :: P.Parser Value
|
||||
types = P.try bool P.<|> P.try operator P.<|> number
|
||||
|
||||
|
||||
parser :: P.Parser [Value]
|
||||
parser = (P.sepBy (P.try operator P.<|> number) P.spaces) <* P.eof
|
||||
parser = (P.sepBy types P.spaces) <* P.eof
|
||||
|
||||
parse :: String -> [Value]
|
||||
parse input = case P.parse parser (trim input) (trim input) of
|
||||
|
@@ -2,11 +2,13 @@ module BC.Types where
|
||||
|
||||
data Value = BInt Integer
|
||||
| BFloat Double
|
||||
| BBool Bool
|
||||
| BOp String
|
||||
| BErr String
|
||||
instance Show Value where
|
||||
show (BInt i) = show i
|
||||
show (BFloat f) = show f
|
||||
show (BBool b) = if b then "true" else "false"
|
||||
show (BOp o) = o
|
||||
show (BErr e) = "error: " ++ e
|
||||
|
||||
|
Reference in New Issue
Block a user