mirror of
https://github.com/IHaskell/IHaskell.git
synced 2025-04-15 19:06:06 +00:00
Added handling of repeated empty lines
This commit is contained in:
parent
c73ad0e684
commit
a73ac76b79
13
Hspec.hs
13
Hspec.hs
@ -144,6 +144,9 @@ layoutChunkerTests = describe "Layout Chunk" $ do
|
||||
it "chunks 'a\\n string\\nextra'" $
|
||||
layoutChunks "a\n string\nextra" `shouldBe` ["a\n string","extra"]
|
||||
|
||||
it "chunks strings with too many lines" $
|
||||
layoutChunks "a\n\nstring" `shouldBe` ["a","string"]
|
||||
|
||||
moduleNameTests = describe "Get Module Name" $ do
|
||||
it "parses simple module names" $
|
||||
"module A where\nx = 3" `named` ["A"]
|
||||
@ -275,3 +278,13 @@ parseStringTests = describe "Parser" $ do
|
||||
parses "data X = 3" `like` [
|
||||
ParseError (Loc 1 10) "Illegal literal in type (use -XDataKinds to enable): 3"
|
||||
]
|
||||
|
||||
it "parses statements after imports" $ do
|
||||
parses "import X\nprint 3" `like` [
|
||||
Import "import X",
|
||||
Expression "print 3"
|
||||
]
|
||||
parses "import X\n\n\nprint 3" `like` [
|
||||
Import "import X",
|
||||
Expression "print 3"
|
||||
]
|
||||
|
@ -42,6 +42,17 @@ build-type: Custom
|
||||
-- Constraint on the version of Cabal needed to build this package.
|
||||
cabal-version: >=1.8
|
||||
|
||||
extra-source-files:
|
||||
config/custom.js
|
||||
config/ipython_config.py
|
||||
config/ipython_console_config.py
|
||||
config/ipython_notebook_config.py
|
||||
config/ipython_qtconsole_config.py
|
||||
deps/codecell.js
|
||||
deps/tooltip.js
|
||||
build-parser.sh
|
||||
images/ihaskell-logo.png
|
||||
|
||||
library
|
||||
build-depends: base ==4.6.*,
|
||||
hspec,
|
||||
@ -91,6 +102,10 @@ executable IHaskell
|
||||
IHaskell.Types
|
||||
IHaskell.ZeroMQ
|
||||
IHaskell.Display
|
||||
IHaskell.Config
|
||||
IHaskell.GHC.HaskellParser
|
||||
|
||||
|
||||
|
||||
|
||||
extensions: DoAndIfThenElse
|
||||
|
@ -95,8 +95,7 @@ type Interpreter = Ghc
|
||||
|
||||
globalImports :: [String]
|
||||
globalImports =
|
||||
[ "import IHaskell.Types"
|
||||
, "import IHaskell.Display"
|
||||
[ "import IHaskell.Display"
|
||||
, "import Control.Applicative ((<$>))"
|
||||
, "import GHC.IO.Handle (hDuplicateTo, hDuplicate)"
|
||||
, "import System.IO"
|
||||
@ -213,8 +212,8 @@ evalCommand (Module contents) = wrapExecution $ do
|
||||
writeFile (fpFromString $ directory ++ filename) contents
|
||||
|
||||
-- Clear old modules of this name
|
||||
let moduleName = intercalate "." namePieces
|
||||
removeTarget $ TargetModule $ mkModuleName moduleName
|
||||
let modName = intercalate "." namePieces
|
||||
removeTarget $ TargetModule $ mkModuleName modName
|
||||
removeTarget $ TargetFile filename Nothing
|
||||
|
||||
-- Set to use object code for fast running times, as that is the only
|
||||
@ -226,26 +225,50 @@ evalCommand (Module contents) = wrapExecution $ do
|
||||
-- Remember which modules we've loaded before.
|
||||
importedModules <- getContext
|
||||
|
||||
-- Create a new target
|
||||
target <- guessTarget moduleName Nothing
|
||||
addTarget target
|
||||
result <- load LoadAllTargets
|
||||
let -- Get the dot-delimited pieces of hte module name.
|
||||
moduleNameOf :: InteractiveImport -> [String]
|
||||
moduleNameOf (IIDecl decl) = split "." . moduleNameString . unLoc . ideclName $ decl
|
||||
moduleNameOf (IIModule imp) = split "." . moduleNameString $ imp
|
||||
|
||||
-- Reset the context, since loading things screws it up.
|
||||
initializeItVariable
|
||||
-- Return whether this module prevents the loading of the one we're
|
||||
-- trying to load. If a module B exist, we cannot load A.B. All
|
||||
-- modules must have unique last names (where A.B has last name B).
|
||||
-- However, we *can* just reload a module.
|
||||
preventsLoading mod =
|
||||
let pieces = moduleNameOf mod in
|
||||
last namePieces == last pieces && namePieces /= pieces
|
||||
|
||||
-- Add imports
|
||||
importDecl <- parseImportDecl $ "import " ++ moduleName
|
||||
let implicitImport = importDecl { ideclImplicit = True }
|
||||
setContext $ IIDecl implicitImport : importedModules
|
||||
-- If we've loaded anything with the same last name, we can't use this.
|
||||
-- Otherwise, GHC tries to load the original *.hs fails and then fails.
|
||||
case find preventsLoading importedModules of
|
||||
-- If something prevents loading this module, return an error.
|
||||
Just previous ->
|
||||
let prevLoaded = intercalate "." (moduleNameOf previous) in
|
||||
return $ displayError $
|
||||
printf "Can't load module %s because already loaded %s" modName prevLoaded
|
||||
|
||||
-- Switch back to interpreted mode.
|
||||
flags <- getSessionDynFlags
|
||||
setSessionDynFlags flags{ hscTarget = HscInterpreted }
|
||||
-- Since nothing prevents loading the module, compile and load it.
|
||||
Nothing -> do
|
||||
-- Create a new target
|
||||
target <- guessTarget modName Nothing
|
||||
addTarget target
|
||||
result <- load LoadAllTargets
|
||||
|
||||
case result of
|
||||
Succeeded -> return []
|
||||
Failed -> return $ displayError $ "Failed to load module " ++ moduleName
|
||||
-- Reset the context, since loading things screws it up.
|
||||
initializeItVariable
|
||||
|
||||
-- Add imports
|
||||
importDecl <- parseImportDecl $ "import " ++ modName
|
||||
let implicitImport = importDecl { ideclImplicit = True }
|
||||
setContext $ IIDecl implicitImport : importedModules
|
||||
|
||||
-- Switch back to interpreted mode.
|
||||
flags <- getSessionDynFlags
|
||||
setSessionDynFlags flags{ hscTarget = HscInterpreted }
|
||||
|
||||
case result of
|
||||
Succeeded -> return []
|
||||
Failed -> return $ displayError $ "Failed to load module " ++ modName
|
||||
|
||||
evalCommand (Directive SetExtension exts) = wrapExecution $ do
|
||||
results <- mapM setExtension (words exts)
|
||||
|
@ -307,7 +307,7 @@ splitAtLoc line col string =
|
||||
-- beyond the indentation of the first line. This parses Haskell layout
|
||||
-- rules properly, and allows using multiline expressions via indentation.
|
||||
layoutChunks :: String -> [String]
|
||||
layoutChunks string = layoutLines (lines string)
|
||||
layoutChunks string = filter (not . null . strip) $ layoutLines $ lines string
|
||||
where
|
||||
layoutLines :: [String] -> [String]
|
||||
-- Empty string case. If there's no input, output is empty.
|
||||
|
Loading…
x
Reference in New Issue
Block a user