primitives: added all necessary primitives
This commit is contained in:
@@ -11,11 +11,14 @@ The idea behind `bc` is to display partial results to the right of the
|
||||
cursor in yellow while we type. A little example can be found in the video
|
||||
above. Minor syntactic cleanups have been developed as well (e.g. no `local`
|
||||
keyword). We have infinite precision integers and 90 decimal mantissa precision
|
||||
floats.
|
||||
floats (similar to setting `scale` to 90).
|
||||
|
||||
We support all builtin functions, but have no IO (no `print`).
|
||||
|
||||
## TODO
|
||||
|
||||
- A good readline copy (haskeline is sadly out of the question for this project)
|
||||
- Add keyboard shortcuts
|
||||
- Comment parsing
|
||||
- Closures that can modify the parent environment (but do away with the `local` keyword).
|
||||
- Better arbitrary precision floats
|
||||
|
8
bc.cabal
8
bc.cabal
@@ -14,6 +14,12 @@ cabal-version: >=1.10
|
||||
executable bc
|
||||
main-is: Main.hs
|
||||
hs-source-dirs: src/
|
||||
build-depends: base >=4.9 && <4.10, directory, hashmap, numbers, parsec, strict, unix
|
||||
build-depends: base >=4.9 && <4.10,
|
||||
directory,
|
||||
hashmap,
|
||||
numbers,
|
||||
parsec,
|
||||
strict,
|
||||
unix
|
||||
hs-source-dirs: src
|
||||
default-language: Haskell2010
|
||||
|
11
src/BC/C.hs
Normal file
11
src/BC/C.hs
Normal file
@@ -0,0 +1,11 @@
|
||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||
module BC.C where
|
||||
|
||||
import Foreign
|
||||
import Foreign.C.Types
|
||||
|
||||
foreign import ccall unsafe "math.h jn"
|
||||
c_jn :: CInt -> CDouble -> CDouble
|
||||
|
||||
jn :: (Real a, Fractional a) => Integer -> a -> a
|
||||
jn x y = realToFrac $ c_jn (fromIntegral x) (realToFrac y)
|
@@ -1,5 +1,6 @@
|
||||
module BC.Primitives where
|
||||
|
||||
import BC.C
|
||||
import BC.Types
|
||||
|
||||
primitives :: [(String, Value)]
|
||||
@@ -8,19 +9,48 @@ primitives = map valuize primitivesList
|
||||
|
||||
|
||||
primitivesList :: [(String, [Value] -> Value)]
|
||||
primitivesList = [ ("cos", pcos)
|
||||
primitivesList = [ ("c", pcos)
|
||||
, ("s", psine)
|
||||
, ("a", parc)
|
||||
, ("l", plog)
|
||||
, ("e", ppow)
|
||||
, ("j", pbessel)
|
||||
, ("sqrt", psqrt)
|
||||
]
|
||||
|
||||
|
||||
pmath :: (BF -> BF) -> [Value] -> Value
|
||||
pmath f [BNum (BInt x)] = BNum $ BFloat $ f $ fromIntegral x
|
||||
pmath f [BNum (BFloat x)] = BNum $ BFloat $ f x
|
||||
pmath f [x] = BErr $ "Expected argument to be a number, got " ++ show x
|
||||
pmath f x = BErr $ "Expected exactly one argument, got " ++ (show $ length x)
|
||||
|
||||
|
||||
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
|
||||
psqrt = pmath sqrt
|
||||
|
||||
|
||||
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
|
||||
pcos = pmath cos
|
||||
|
||||
psine :: [Value] -> Value
|
||||
psine = pmath sin
|
||||
|
||||
parc :: [Value] -> Value
|
||||
parc = pmath atan
|
||||
|
||||
plog :: [Value] -> Value
|
||||
plog = pmath log
|
||||
|
||||
e :: BF
|
||||
e = exp 1
|
||||
|
||||
ppow :: [Value] -> Value
|
||||
ppow = pmath (e **)
|
||||
|
||||
pbessel :: [Value] -> Value
|
||||
pbessel [BNum (BInt x), BNum (BInt y)] = BNum $ BFloat $ jn x $ fromIntegral y
|
||||
pbessel [BNum (BInt x), BNum (BFloat y)] = BNum $ BFloat $ jn x y
|
||||
pbessel [x, BNum _] = BErr $ "Expected argument to be an integer, got " ++ show x
|
||||
pbessel [_, x] = BErr $ "Expected argument to be a number, got " ++ show x
|
||||
pbessel x = BErr $ "Expected exactly two arguments, got " ++ (show $ length x)
|
||||
|
@@ -38,9 +38,12 @@ instance Show Value where
|
||||
show (BNative _) = "native"
|
||||
|
||||
|
||||
type BF = BigFloat (PrecPlus20 (PrecPlus20 Prec50))
|
||||
|
||||
|
||||
-- sorry, this is a little hacky
|
||||
data Number = BInt Integer
|
||||
| BFloat (BigFloat (PrecPlus20 (PrecPlus20 Prec50)))
|
||||
| BFloat BF
|
||||
deriving (Ord, Eq)
|
||||
instance Show Number where
|
||||
show (BInt i) = show i
|
||||
|
Reference in New Issue
Block a user