Skip to content

Commit

Permalink
Adding testing for evaluation
Browse files Browse the repository at this point in the history
  • Loading branch information
gibiansky committed Dec 14, 2013
1 parent b404f29 commit 324f5c5
Show file tree
Hide file tree
Showing 2 changed files with 89 additions and 2 deletions.
88 changes: 88 additions & 0 deletions Hspec.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,17 @@
{-# LANGUAGE QuasiQuotes #-}
import GHC
import GHC.Paths
import Data.IORef
import Control.Monad
import Data.List
import System.Directory
import Data.String.Here
import Data.String.Utils (strip)

import IHaskell.Eval.Parser
import IHaskell.Types
import IHaskell.IPython
import IHaskell.Eval.Evaluate

import Test.Hspec
import Test.Hspec.HUnit
Expand All @@ -16,11 +26,89 @@ is string blockType = do
result <- doGhc $ parseString string
result `shouldBe` [blockType string]

eval string = do
outputAccum <- newIORef []
let publish displayDatas = liftIO $ modifyIORef outputAccum (displayDatas :)
getTemporaryDirectory >>= setCurrentDirectory
interpret $ evaluate 1 string publish
out <- readIORef outputAccum
return $ reverse out

becomes string expected = do
let indent (' ':x) = 1 + indent x
indent _ = 0
empty = null . strip
stringLines = filter (not . empty) $ lines string
minIndent = minimum (map indent stringLines)
newString = unlines $ map (drop minIndent) stringLines
eval newString >>= comparison
where
comparison results = do
when (length results /= length expected) $
expectationFailure $ "Expected result to have " ++ show (length expected)
++ " results. Got " ++ show results

let isPlain (Display PlainText _) = True
isPlain _ = False

forM_ (zip results expected) $ \(result, expected) ->
case find isPlain result of
Just (Display PlainText str) -> expected `shouldBe` str
Nothing -> expectationFailure $ "No plain-text output in " ++ show result



main :: IO ()
main = hspec $ do
parserTests
ipythonTests
evalTests

evalTests = do
describe "Code Evaluation" $ do
it "evaluates expressions" $ do
"3" `becomes` ["3"]
"3+5" `becomes` ["8"]
"print 3" `becomes` ["3"]
[hereLit|
let x = 11
z = 10 in
x+z
|] `becomes` ["21"]

it "evaluates multiline expressions" $ do
[hereLit|
import Control.Monad
forM_ [1, 2, 3] $ \x ->
print x
|] `becomes` ["1\n2\n3"]

it "evaluates function declarations silently" $ do
[hereLit|
fun :: [Int] -> Int
fun [] = 3
fun (x:xs) = 10
fun [1, 2]
|] `becomes` ["10"]

it "evaluates data declarations" $ do
[hereLit|
data X = Y Int
| Z String
deriving (Show, Eq)
print [Y 3, Z "No"]
print (Y 3 == Z "No")
|] `becomes` ["[Y 3,Z \"No\"]", "False"]

it "is silent for imports" $ do
"import Control.Monad" `becomes` []
"import qualified Control.Monad" `becomes` []
"import qualified Control.Monad as CM" `becomes` []
"import Control.Monad (when)" `becomes` []

it "evaluates directives" $ do
":typ 3" `becomes` ["forall a. Num a => a"]
":in String" `becomes` ["type String = [Char] \t-- Defined in `GHC.Base'"]

ipythonTests = do
describe "Parse IPython Version" $ do
Expand Down
3 changes: 1 addition & 2 deletions IHaskell/Eval/Evaluate.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,8 +4,7 @@
This module exports all functions used for evaluation of IHaskell input.
-}
module IHaskell.Eval.Evaluate (
interpret, evaluate, Interpreter, liftIO,
typeCleaner
interpret, evaluate, Interpreter, liftIO, typeCleaner
) where

import ClassyPrelude hiding (liftIO, hGetContents)
Expand Down

0 comments on commit 324f5c5

Please sign in to comment.