all: added primitives
This commit is contained in:
@@ -51,6 +51,7 @@ eval state [BBraced vals] = eval state vals
|
||||
eval state [BCall (BSym name) args] =
|
||||
case M.lookup name state of
|
||||
Just val@BFun{} -> funCall state val args
|
||||
Just val@BNative{} -> funCall state val args
|
||||
Nothing -> (BErr ("function " ++ name ++ " is undefined"), state)
|
||||
_ -> (BErr (name ++ " is not a function"), state)
|
||||
eval state [] = (BSym "", state)
|
||||
@@ -134,3 +135,7 @@ funCall state (BFun name args body) provided =
|
||||
callWith state (a:args) (p:provided) =
|
||||
let (evald, nstate) = eval state p
|
||||
in callWith (M.insert a evald nstate) args provided
|
||||
-- TODO: fix state forgetfulness
|
||||
funCall state (BNative body) provided =
|
||||
let args = map (fst . (eval state)) provided
|
||||
in (body args, state)
|
||||
|
@@ -35,7 +35,7 @@ float = do
|
||||
Just "-" -> return $ construct ("-" ++ x ++ "." ++ y)
|
||||
_ -> return $ construct (x ++ "." ++ y)
|
||||
-- do a little dance
|
||||
where construct str = BNum $ BFloat $ fromRational $ realToFrac $ (read str::Double)
|
||||
where construct str = BNum $ BFloat $ fromRational $ realToFrac (read str::Double)
|
||||
|
||||
|
||||
integer :: P.Parser Value
|
||||
|
26
src/BC/Primitives.hs
Normal file
26
src/BC/Primitives.hs
Normal file
@@ -0,0 +1,26 @@
|
||||
module BC.Primitives where
|
||||
|
||||
import BC.Types
|
||||
|
||||
primitives :: [(String, Value)]
|
||||
primitives = map valuize primitivesList
|
||||
where valuize (x, y) = (x, BNative y)
|
||||
|
||||
|
||||
primitivesList :: [(String, [Value] -> Value)]
|
||||
primitivesList = [ ("cos", pcos)
|
||||
, ("sqrt", psqrt)
|
||||
]
|
||||
|
||||
|
||||
psqrt :: [Value] -> Value
|
||||
psqrt [BNum (BInt x)] = BNum $ BFloat $ sqrt $ fromIntegral x
|
||||
psqrt [BNum (BFloat x)] = BNum $ BFloat $ sqrt x
|
||||
psqrt [x] = BErr $ "Expected argument to be a number, got " ++ show x
|
||||
|
||||
|
||||
pcos :: [Value] -> Value
|
||||
pcos [BNum (BInt x)] = BNum $ BFloat $ cos $ fromIntegral x
|
||||
pcos [BNum (BFloat x)] = BNum $ BFloat $ cos x
|
||||
pcos [x] = BErr $ "Expected argument to be a number, got " ++ show x
|
||||
|
@@ -2,9 +2,10 @@ module BC.State where
|
||||
|
||||
import Data.HashMap
|
||||
|
||||
import BC.Primitives
|
||||
import BC.Types
|
||||
|
||||
type State = Map String Value
|
||||
|
||||
newState :: State
|
||||
newState = empty
|
||||
newState = fromList primitives
|
||||
|
@@ -35,6 +35,7 @@ instance Show Value where
|
||||
show (BSym o) = o
|
||||
show (BNum n) = show n
|
||||
show (BErr e) = "error: " ++ e
|
||||
show (BNative _) = "native"
|
||||
|
||||
|
||||
-- sorry, this is a little hacky
|
||||
|
Reference in New Issue
Block a user