2013-12-14 10:44:45 -08:00
|
|
|
{-# LANGUAGE QuasiQuotes #-}
|
2014-01-02 23:07:07 -05:00
|
|
|
module Main where
|
2014-01-05 20:57:08 -05:00
|
|
|
import Prelude
|
2013-12-13 18:00:41 -08:00
|
|
|
import GHC
|
|
|
|
import GHC.Paths
|
2013-12-14 10:44:45 -08:00
|
|
|
import Data.IORef
|
|
|
|
import Control.Monad
|
2014-01-05 17:49:29 -05:00
|
|
|
import Control.Monad.Trans ( MonadIO, liftIO )
|
2013-12-14 10:44:45 -08:00
|
|
|
import Data.List
|
|
|
|
import System.Directory
|
2014-01-05 17:49:29 -05:00
|
|
|
import Shelly (Sh, shelly, cmd, (</>), toTextIgnore, cd, withTmpDir)
|
|
|
|
import Filesystem.Path.CurrentOS (encodeString)
|
2013-12-14 10:44:45 -08:00
|
|
|
import Data.String.Here
|
2013-12-17 21:47:59 -08:00
|
|
|
import Data.String.Utils (strip, replace)
|
2014-01-02 16:09:26 -05:00
|
|
|
import Data.Monoid
|
2013-12-14 10:44:45 -08:00
|
|
|
|
2013-12-13 18:00:41 -08:00
|
|
|
import IHaskell.Eval.Parser
|
2013-12-14 10:44:45 -08:00
|
|
|
import IHaskell.Types
|
2013-12-13 18:00:41 -08:00
|
|
|
import IHaskell.IPython
|
2014-01-05 17:49:29 -05:00
|
|
|
import IHaskell.Eval.Evaluate as Eval hiding (liftIO)
|
2014-01-05 21:52:52 -05:00
|
|
|
import qualified IHaskell.Eval.Evaluate as Eval (liftIO)
|
|
|
|
|
2013-12-17 21:47:59 -08:00
|
|
|
import IHaskell.Eval.Completion
|
2013-12-13 18:00:41 -08:00
|
|
|
|
2014-01-05 21:52:52 -05:00
|
|
|
import Debug.Trace
|
|
|
|
|
2013-12-13 18:00:41 -08:00
|
|
|
import Test.Hspec
|
|
|
|
import Test.Hspec.HUnit
|
|
|
|
|
|
|
|
doGhc = runGhc (Just libdir)
|
|
|
|
|
2013-12-29 17:58:02 -05:00
|
|
|
parses str = do
|
|
|
|
res <- doGhc $ parseString str
|
|
|
|
return $ map unloc res
|
2013-12-13 18:00:41 -08:00
|
|
|
|
|
|
|
like parser desired = parser >>= (`shouldBe` desired)
|
|
|
|
|
|
|
|
is string blockType = do
|
|
|
|
result <- doGhc $ parseString string
|
2013-12-29 17:58:02 -05:00
|
|
|
map unloc result `shouldBe` [blockType $ strip string]
|
2013-12-13 18:00:41 -08:00
|
|
|
|
2013-12-14 10:44:45 -08:00
|
|
|
eval string = do
|
|
|
|
outputAccum <- newIORef []
|
2014-01-02 16:29:26 -05:00
|
|
|
let publish final displayDatas = when final $ modifyIORef outputAccum (displayDatas :)
|
2013-12-14 10:44:45 -08:00
|
|
|
getTemporaryDirectory >>= setCurrentDirectory
|
2014-01-04 20:13:06 -05:00
|
|
|
let state = defaultKernelState { getLintStatus = LintOff }
|
2013-12-29 17:58:02 -05:00
|
|
|
interpret $ Eval.evaluate state string publish
|
2013-12-14 10:44:45 -08:00
|
|
|
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
|
2014-01-05 20:57:08 -05:00
|
|
|
where
|
2013-12-14 10:44:45 -08:00
|
|
|
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
|
2013-12-16 21:48:26 -08:00
|
|
|
Just (Display PlainText str) -> str `shouldBe` expected
|
2013-12-14 10:44:45 -08:00
|
|
|
Nothing -> expectationFailure $ "No plain-text output in " ++ show result
|
|
|
|
|
2013-12-17 21:47:59 -08:00
|
|
|
completes string expected = completionTarget newString cursorloc `shouldBe` expected
|
2013-12-24 17:00:10 -05:00
|
|
|
where (newString, cursorloc) = case elemIndex '!' string of
|
2013-12-17 21:47:59 -08:00
|
|
|
Nothing -> error "Expected cursor written as '!'."
|
|
|
|
Just idx -> (replace "!" "" string, idx)
|
|
|
|
|
2014-01-06 12:28:07 -05:00
|
|
|
completionHas_ wrap string expected = do
|
2013-12-17 21:47:59 -08:00
|
|
|
(matched, completions) <- doGhc $ do
|
2014-01-06 12:39:58 -05:00
|
|
|
wrap $ do initCompleter
|
2014-01-06 12:28:07 -05:00
|
|
|
complete newString cursorloc
|
2014-01-05 17:49:29 -05:00
|
|
|
let existsInCompletion = (`elem` completions)
|
2013-12-17 21:47:59 -08:00
|
|
|
unmatched = filter (not . existsInCompletion) expected
|
|
|
|
unmatched `shouldBe` []
|
2013-12-24 17:00:10 -05:00
|
|
|
where (newString, cursorloc) = case elemIndex '!' string of
|
2013-12-17 21:47:59 -08:00
|
|
|
Nothing -> error "Expected cursor written as '!'."
|
|
|
|
Just idx -> (replace "!" "" string, idx)
|
|
|
|
|
2014-01-06 12:28:07 -05:00
|
|
|
completionHas = completionHas_ id
|
2014-01-05 20:52:39 -05:00
|
|
|
|
2014-01-06 12:28:07 -05:00
|
|
|
initCompleter :: GhcMonad m => m ()
|
|
|
|
initCompleter = do
|
|
|
|
pwd <- Eval.liftIO $ getCurrentDirectory
|
|
|
|
--Eval.liftIO $ traceIO $ pwd
|
2013-12-17 21:47:59 -08:00
|
|
|
flags <- getSessionDynFlags
|
|
|
|
setSessionDynFlags $ flags { hscTarget = HscInterpreted, ghcLink = LinkInMemory }
|
|
|
|
|
|
|
|
-- Import modules.
|
|
|
|
imports <- mapM parseImportDecl ["import Prelude",
|
2014-01-05 20:52:39 -05:00
|
|
|
"import qualified Control.Monad",
|
|
|
|
"import qualified Data.List as List",
|
|
|
|
"import Data.Maybe as Maybe"]
|
2013-12-17 21:47:59 -08:00
|
|
|
setContext $ map IIDecl imports
|
2013-12-13 18:00:41 -08:00
|
|
|
|
2014-01-05 20:52:39 -05:00
|
|
|
withHsDirectory :: (FilePath -> Sh ()) -> IO ()
|
2014-01-05 20:57:08 -05:00
|
|
|
withHsDirectory f = shelly $ withTmpDir $ \dirPath ->
|
|
|
|
do cd dirPath
|
2014-01-05 17:49:29 -05:00
|
|
|
cmd "mkdir" $ "" </> "dir"
|
|
|
|
cmd "mkdir" $ "dir" </> "dir1"
|
|
|
|
cmd "touch" "file1.hs" "dir/file2.hs" "file1.lhs" "dir/file2.lhs"
|
2014-01-05 20:52:39 -05:00
|
|
|
f $ encodeString dirPath
|
2014-01-04 21:05:52 -05:00
|
|
|
|
2013-12-13 18:00:41 -08:00
|
|
|
main :: IO ()
|
|
|
|
main = hspec $ do
|
|
|
|
parserTests
|
2013-12-14 10:44:45 -08:00
|
|
|
evalTests
|
2013-12-17 21:47:59 -08:00
|
|
|
completionTests
|
|
|
|
|
|
|
|
completionTests = do
|
|
|
|
describe "Completion" $ do
|
|
|
|
it "correctly gets the completion identifier without dots" $ do
|
2013-12-17 21:51:21 -08:00
|
|
|
"hello!" `completes` ["hello"]
|
2013-12-17 21:47:59 -08:00
|
|
|
"hello aa!bb goodbye" `completes` ["aa"]
|
|
|
|
"hello aabb! goodbye" `completes` ["aabb"]
|
2013-12-17 21:51:21 -08:00
|
|
|
"aacc! goodbye" `completes` ["aacc"]
|
2013-12-17 21:47:59 -08:00
|
|
|
"hello !aabb goodbye" `completes` []
|
2013-12-17 21:51:21 -08:00
|
|
|
"!aabb goodbye" `completes` []
|
2013-12-17 21:47:59 -08:00
|
|
|
|
|
|
|
it "correctly gets the completion identifier with dots" $ do
|
|
|
|
"hello test.aa!bb goodbye" `completes` ["test", "aa"]
|
2013-12-17 21:51:21 -08:00
|
|
|
"Test.!" `completes` ["Test", ""]
|
|
|
|
"Test.Thing!" `completes` ["Test", "Thing"]
|
|
|
|
"Test.Thing.!" `completes` ["Test", "Thing", ""]
|
|
|
|
"Test.Thing.!nope" `completes` ["Test", "Thing", ""]
|
2013-12-17 21:47:59 -08:00
|
|
|
|
|
|
|
it "correctly gets the completion type" $ do
|
2013-12-17 21:51:21 -08:00
|
|
|
completionType "import Data." ["Data", ""] `shouldBe` ModuleName "Data" ""
|
|
|
|
completionType "import Prel" ["Prel"] `shouldBe` ModuleName "" "Prel"
|
|
|
|
completionType "import D.B.M" ["D", "B", "M"] `shouldBe` ModuleName "D.B" "M"
|
|
|
|
completionType " import A." ["A", ""] `shouldBe` ModuleName "A" ""
|
|
|
|
completionType "import a.x" ["a", "x"] `shouldBe` Identifier "x"
|
|
|
|
completionType "A.x" ["A", "x"] `shouldBe` Qualified "A" "x"
|
|
|
|
completionType "a.x" ["a", "x"] `shouldBe` Identifier "x"
|
|
|
|
completionType "pri" ["pri"] `shouldBe` Identifier "pri"
|
2014-01-06 12:28:07 -05:00
|
|
|
completionType ":load A" ["A"] `shouldBe` HsFilePath "A"
|
2013-12-17 21:47:59 -08:00
|
|
|
|
|
|
|
it "properly completes identifiers" $ do
|
2013-12-17 21:51:21 -08:00
|
|
|
"pri!" `completionHas` ["print"]
|
|
|
|
"ma!" `completionHas` ["map"]
|
|
|
|
"hello ma!" `completionHas` ["map"]
|
2013-12-17 21:47:59 -08:00
|
|
|
"print $ catMa!" `completionHas` ["catMaybes"]
|
|
|
|
|
|
|
|
it "properly completes qualified identifiers" $ do
|
2013-12-17 21:51:21 -08:00
|
|
|
"Control.Monad.liftM!" `completionHas` [ "Control.Monad.liftM"
|
|
|
|
, "Control.Monad.liftM2"
|
|
|
|
, "Control.Monad.liftM5"]
|
|
|
|
"print $ List.intercal!" `completionHas` ["List.intercalate"]
|
2013-12-17 21:47:59 -08:00
|
|
|
"print $ Data.Maybe.cat!" `completionHas` ["Data.Maybe.catMaybes"]
|
2013-12-17 21:51:21 -08:00
|
|
|
"print $ Maybe.catM!" `completionHas` ["Maybe.catMaybes"]
|
2013-12-17 21:47:59 -08:00
|
|
|
|
|
|
|
it "properly completes imports" $ do
|
2013-12-17 21:51:21 -08:00
|
|
|
"import Data.!" `completionHas` ["Data.Maybe", "Data.List"]
|
2013-12-17 21:47:59 -08:00
|
|
|
"import Data.M!" `completionHas` ["Data.Maybe"]
|
2013-12-17 21:51:21 -08:00
|
|
|
"import Prel!" `completionHas` ["Prelude"]
|
2013-12-14 10:44:45 -08:00
|
|
|
|
2014-01-05 20:57:08 -05:00
|
|
|
it "properly completes haskell file paths on :load directive" $
|
|
|
|
withHsDirectory $ \dirPath ->
|
2014-01-05 20:52:39 -05:00
|
|
|
let loading xs = ":load " ++ encodeString xs
|
|
|
|
paths xs = map encodeString xs
|
2014-01-06 12:39:58 -05:00
|
|
|
completionHas' = completionHas_ fun
|
2014-01-06 12:28:07 -05:00
|
|
|
fun action = do pwd <- Eval.liftIO getCurrentDirectory
|
|
|
|
Eval.evaluate defaultKernelState
|
|
|
|
(":! cd " ++ dirPath)
|
2014-01-06 12:39:58 -05:00
|
|
|
(\b d -> return ())
|
|
|
|
out <- action
|
2014-01-06 12:28:07 -05:00
|
|
|
Eval.evaluate defaultKernelState
|
|
|
|
(":! cd " ++ pwd)
|
2014-01-06 12:39:58 -05:00
|
|
|
(\b d -> return ())
|
2014-01-06 12:28:07 -05:00
|
|
|
return out
|
2014-01-05 20:57:08 -05:00
|
|
|
in liftIO $ do
|
2014-01-05 20:52:39 -05:00
|
|
|
loading ("dir" </> "file!") `completionHas'` paths ["dir" </> "file2.hs",
|
|
|
|
"dir" </> "file2.lhs"]
|
|
|
|
loading ("" </> "file1!") `completionHas'` paths ["" </> "file1.hs",
|
2014-01-06 12:28:07 -05:00
|
|
|
"" </> "file1.lhs"]
|
|
|
|
loading ("" </> "file1!") `completionHas'` paths ["" </> "file1.hs",
|
|
|
|
"" </> "file1.lhs"]
|
2014-01-05 21:52:52 -05:00
|
|
|
|
2013-12-14 10:44:45 -08:00
|
|
|
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"]
|
|
|
|
|
2013-12-16 21:48:26 -08:00
|
|
|
it "evaluates do blocks in expressions" $ do
|
|
|
|
[hereLit|
|
|
|
|
show (show (do
|
|
|
|
Just 10
|
|
|
|
Nothing
|
|
|
|
Just 100))
|
|
|
|
|] `becomes` ["\"\\\"Nothing\\\"\""]
|
|
|
|
|
2013-12-14 10:44:45 -08:00
|
|
|
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'"]
|
2013-12-13 18:00:41 -08:00
|
|
|
|
|
|
|
parserTests = do
|
|
|
|
layoutChunkerTests
|
|
|
|
moduleNameTests
|
|
|
|
parseStringTests
|
|
|
|
|
|
|
|
layoutChunkerTests = describe "Layout Chunk" $ do
|
|
|
|
it "chunks 'a string'" $
|
2014-01-02 16:29:26 -05:00
|
|
|
map unloc (layoutChunks "a string") `shouldBe` ["a string"]
|
2013-12-13 18:00:41 -08:00
|
|
|
|
2014-01-02 16:29:26 -05:00
|
|
|
it "chunks 'a\\n string'" $
|
|
|
|
map unloc (layoutChunks "a\n string") `shouldBe` ["a\n string"]
|
2013-12-13 18:00:41 -08:00
|
|
|
|
|
|
|
it "chunks 'a\\n string\\nextra'" $
|
2014-01-02 16:29:26 -05:00
|
|
|
map unloc (layoutChunks "a\n string\nextra") `shouldBe` ["a\n string","extra"]
|
2013-12-13 18:00:41 -08:00
|
|
|
|
2013-12-14 14:22:58 -08:00
|
|
|
it "chunks strings with too many lines" $
|
2014-01-02 16:29:26 -05:00
|
|
|
map unloc (layoutChunks "a\n\nstring") `shouldBe` ["a","string"]
|
|
|
|
|
|
|
|
it "parses multiple exprs" $ do
|
|
|
|
let text = [hereLit|
|
|
|
|
first
|
|
|
|
|
|
|
|
second
|
|
|
|
third
|
|
|
|
|
|
|
|
fourth
|
|
|
|
|]
|
|
|
|
layoutChunks text `shouldBe`
|
|
|
|
[Located 2 "first",
|
|
|
|
Located 4 "second",
|
|
|
|
Located 5 "third",
|
|
|
|
Located 7 "fourth"]
|
2013-12-14 14:22:58 -08:00
|
|
|
|
2013-12-13 18:00:41 -08:00
|
|
|
moduleNameTests = describe "Get Module Name" $ do
|
|
|
|
it "parses simple module names" $
|
|
|
|
"module A where\nx = 3" `named` ["A"]
|
|
|
|
it "parses module names with dots" $
|
|
|
|
"module A.B where\nx = 3" `named` ["A", "B"]
|
|
|
|
it "parses module names with exports" $
|
|
|
|
"module A.B.C ( x ) where x = 3" `named` ["A", "B", "C"]
|
|
|
|
it "errors when given unnamed modules" $ do
|
|
|
|
doGhc (getModuleName "x = 3") `shouldThrow` anyException
|
|
|
|
where
|
|
|
|
named str result = do
|
|
|
|
res <- doGhc $ getModuleName str
|
|
|
|
res `shouldBe` result
|
|
|
|
|
|
|
|
parseStringTests = describe "Parser" $ do
|
|
|
|
it "parses empty strings" $
|
|
|
|
parses "" `like` []
|
|
|
|
|
|
|
|
it "parses simple imports" $
|
|
|
|
"import Data.Monoid" `is` Import
|
|
|
|
|
|
|
|
it "parses simple arithmetic" $
|
|
|
|
"3 + 5" `is` Expression
|
|
|
|
|
|
|
|
it "parses :type" $
|
|
|
|
parses ":type x\n:ty x" `like` [
|
|
|
|
Directive GetType "x",
|
|
|
|
Directive GetType "x"
|
|
|
|
]
|
|
|
|
|
|
|
|
it "parses :info" $
|
|
|
|
parses ":info x\n:in x" `like` [
|
|
|
|
Directive GetInfo "x",
|
|
|
|
Directive GetInfo "x"
|
|
|
|
]
|
|
|
|
|
|
|
|
it "parses :help and :?" $
|
|
|
|
parses ":? x\n:help x" `like` [
|
|
|
|
Directive GetHelp "x",
|
|
|
|
Directive GetHelp "x"
|
|
|
|
]
|
|
|
|
|
|
|
|
it "parses :set x" $
|
|
|
|
parses ":set x" `like` [
|
2014-01-04 20:13:06 -05:00
|
|
|
Directive SetOpt "x"
|
2013-12-13 18:00:41 -08:00
|
|
|
]
|
|
|
|
|
|
|
|
it "parses :extension x" $
|
|
|
|
parses ":ex x\n:extension x" `like` [
|
|
|
|
Directive SetExtension "x",
|
|
|
|
Directive SetExtension "x"
|
|
|
|
]
|
|
|
|
|
2014-01-05 20:57:08 -05:00
|
|
|
it "fails to parse :nope" $
|
2013-12-13 18:00:41 -08:00
|
|
|
parses ":nope goodbye" `like` [
|
|
|
|
ParseError (Loc 1 1) "Unknown directive: 'nope'."
|
|
|
|
]
|
|
|
|
|
|
|
|
it "parses number followed by let stmt" $
|
|
|
|
parses "3\nlet x = expr" `like` [
|
|
|
|
Expression "3",
|
|
|
|
Statement "let x = expr"
|
|
|
|
]
|
|
|
|
|
|
|
|
it "parses let x in y" $
|
|
|
|
"let x = 3 in x + 3" `is` Expression
|
|
|
|
|
|
|
|
it "parses a data declaration" $
|
|
|
|
"data X = Y Int" `is` Declaration
|
|
|
|
|
|
|
|
it "parses number followed by type directive" $
|
|
|
|
parses "3\n:t expr" `like` [
|
|
|
|
Expression "3",
|
|
|
|
Directive GetType "expr"
|
|
|
|
]
|
|
|
|
|
|
|
|
it "parses a <- statement" $
|
|
|
|
"y <- print 'no'" `is` Statement
|
|
|
|
|
|
|
|
it "parses a <- stmt followed by let stmt" $
|
|
|
|
parses "y <- do print 'no'\nlet x = expr" `like` [
|
2013-12-16 21:48:26 -08:00
|
|
|
Statement "y <- do print 'no'",
|
2013-12-13 18:00:41 -08:00
|
|
|
Statement "let x = expr"
|
|
|
|
]
|
|
|
|
|
|
|
|
it "parses <- followed by let followed by expr" $
|
|
|
|
parses "y <- do print 'no'\nlet x = expr\nexpression" `like` [
|
2013-12-16 21:48:26 -08:00
|
|
|
Statement "y <- do print 'no'",
|
2013-12-13 18:00:41 -08:00
|
|
|
Statement "let x = expr",
|
|
|
|
Expression "expression"
|
|
|
|
]
|
|
|
|
|
|
|
|
it "parses two print statements" $
|
|
|
|
parses "print yes\nprint no" `like` [
|
|
|
|
Expression "print yes",
|
|
|
|
Expression "print no"
|
|
|
|
]
|
|
|
|
|
|
|
|
it "parses a pattern-maching function declaration" $
|
|
|
|
"fun [] = 10" `is` Declaration
|
|
|
|
|
|
|
|
it "parses a function decl followed by an expression" $
|
|
|
|
parses "fun [] = 10\nprint 'h'" `like` [
|
|
|
|
Declaration "fun [] = 10",
|
|
|
|
Expression "print 'h'"
|
|
|
|
]
|
|
|
|
|
|
|
|
it "parses list pattern matching fun decl" $
|
|
|
|
"fun (x : xs) = 100" `is` Declaration
|
|
|
|
|
|
|
|
it "parses two pattern matches as the same declaration" $
|
|
|
|
"fun [] = 10\nfun (x : xs) = 100" `is` Declaration
|
|
|
|
|
|
|
|
it "parses a type signature followed by a declaration" $
|
|
|
|
"fun :: [a] -> Int\nfun [] = 10\nfun (x : xs) = 100" `is` Declaration
|
|
|
|
|
|
|
|
it "parases a simple module" $
|
|
|
|
"module A where x = 3" `is` Module
|
|
|
|
|
|
|
|
it "parses a module with an export" $
|
|
|
|
"module B (x) where x = 3" `is` Module
|
|
|
|
|
|
|
|
it "breaks when a let is incomplete" $
|
|
|
|
parses "let x = 3 in" `like` [
|
|
|
|
ParseError (Loc 1 13) "parse error (possibly incorrect indentation or mismatched brackets)"
|
|
|
|
]
|
|
|
|
|
|
|
|
it "breaks without data kinds" $
|
|
|
|
parses "data X = 3" `like` [
|
|
|
|
ParseError (Loc 1 10) "Illegal literal in type (use -XDataKinds to enable): 3"
|
|
|
|
]
|
2013-12-14 14:22:58 -08:00
|
|
|
|
|
|
|
it "parses statements after imports" $ do
|
|
|
|
parses "import X\nprint 3" `like` [
|
|
|
|
Import "import X",
|
2014-01-05 20:57:08 -05:00
|
|
|
Expression "print 3"
|
2013-12-14 14:22:58 -08:00
|
|
|
]
|
2013-12-14 14:43:45 -08:00
|
|
|
parses "import X\n\nprint 3" `like` [
|
2013-12-14 14:22:58 -08:00
|
|
|
Import "import X",
|
2014-01-05 20:57:08 -05:00
|
|
|
Expression "print 3"
|
2013-12-14 14:22:58 -08:00
|
|
|
]
|
2014-01-05 20:57:08 -05:00
|
|
|
it "ignores blank lines properly" $
|
2013-12-25 21:38:11 -05:00
|
|
|
[hereLit|
|
|
|
|
test arg = hello
|
|
|
|
where
|
|
|
|
x = y
|
|
|
|
|
|
|
|
z = w
|
|
|
|
|] `is` Declaration
|
2013-12-16 21:48:26 -08:00
|
|
|
it "doesn't break on long strings" $ do
|
|
|
|
let longString = concat $ replicate 20 "hello "
|
|
|
|
("img ! src \"" ++ longString ++ "\" ! width \"500\"") `is` Expression
|
|
|
|
|
|
|
|
it "parses do blocks in expression" $ do
|
|
|
|
[hereLit|
|
|
|
|
show (show (do
|
|
|
|
Just 10
|
|
|
|
Nothing
|
|
|
|
Just 100))
|
|
|
|
|] `is` Expression
|
2013-12-29 18:06:35 -05:00
|
|
|
it "correctly locates parsed items" $ do
|
|
|
|
let go = doGhc . parseString
|
|
|
|
go [hereLit|
|
|
|
|
first
|
|
|
|
|
|
|
|
second
|
2014-01-02 16:29:26 -05:00
|
|
|
|] >>= (`shouldBe` [Located 2 (Expression "first"),
|
2014-01-05 21:52:52 -05:00
|
|
|
Located 4 (Expression "second")])
|