Commit d87d7e72 authored by Andrew Gibiansky's avatar Andrew Gibiansky

Updated tests and parser to 7.8

parent b748c5b7
{-# LANGUAGE QuasiQuotes, OverloadedStrings, ExtendedDefaultRules #-} {-# LANGUAGE QuasiQuotes, OverloadedStrings, ExtendedDefaultRules, CPP #-}
-- Keep all the language pragmas here so it can be compiled separately. -- Keep all the language pragmas here so it can be compiled separately.
module Main where module Main where
import Prelude import Prelude
...@@ -500,7 +500,11 @@ parseStringTests = describe "Parser" $ do ...@@ -500,7 +500,11 @@ parseStringTests = describe "Parser" $ do
it "breaks without data kinds" $ it "breaks without data kinds" $
parses "data X = 3" `like` [ parses "data X = 3" `like` [
#if MIN_VERSION_ghc(7, 8, 0)
ParseError (Loc 1 10) "Illegal literal in type (use DataKinds to enable): 3"
#else
ParseError (Loc 1 10) "Illegal literal in type (use -XDataKinds to enable): 3" ParseError (Loc 1 10) "Illegal literal in type (use -XDataKinds to enable): 3"
#endif
] ]
it "parses statements after imports" $ do it "parses statements after imports" $ do
......
...@@ -78,7 +78,7 @@ import Data.Version (versionBranch) ...@@ -78,7 +78,7 @@ import Data.Version (versionBranch)
data ErrorOccurred = Success | Failure deriving (Show, Eq) data ErrorOccurred = Success | Failure deriving (Show, Eq)
debug :: Bool debug :: Bool
debug = False debug = True
ignoreTypePrefixes :: [String] ignoreTypePrefixes :: [String]
ignoreTypePrefixes = ["GHC.Types", "GHC.Base", "GHC.Show", "System.IO", ignoreTypePrefixes = ["GHC.Types", "GHC.Base", "GHC.Show", "System.IO",
...@@ -705,6 +705,9 @@ evalCommand output (Expression expr) state = do ...@@ -705,6 +705,9 @@ evalCommand output (Expression expr) state = do
let widgetExpr = printf "(IHaskell.Display.Widget (%s))" expr :: String let widgetExpr = printf "(IHaskell.Display.Widget (%s))" expr :: String
isWidget <- attempt $ exprType widgetExpr isWidget <- attempt $ exprType widgetExpr
write $ "Can Display: " ++ show canRunDisplay
write $ " Is Widget: " ++ show canRunDisplay
if canRunDisplay if canRunDisplay
then do then do
-- Use the display. As a result, `it` is set to the output. -- Use the display. As a result, `it` is set to the output.
......
...@@ -175,8 +175,8 @@ parseCodeChunk code startLine = do ...@@ -175,8 +175,8 @@ parseCodeChunk code startLine = do
parsers flags = parsers flags =
[ (Import, unparser parserImport) [ (Import, unparser parserImport)
, (TypeSignature, unparser parserTypeSignature) , (TypeSignature, unparser parserTypeSignature)
, (Declaration, unparser parserDeclaration)
, (Statement, unparser parserStatement) , (Statement, unparser parserStatement)
, (Declaration, unparser parserDeclaration)
] ]
where where
unparser :: Parser a -> String -> ParseOutput String unparser :: Parser a -> String -> ParseOutput String
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment