Merge pull request #306 from DanielG/dev
Don't fall back to sandbox if cabal file fails to parse
This commit is contained in:
commit
d1cea9a0c7
@ -1,6 +1,7 @@
|
|||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
|
|
||||||
-- | Reading cabal @dist/setup-config@
|
-- | This module facilitates extracting information from Cabal's on-disk
|
||||||
|
-- 'LocalBuildInfo' (@dist/setup-config@).
|
||||||
module Language.Haskell.GhcMod.CabalConfig (
|
module Language.Haskell.GhcMod.CabalConfig (
|
||||||
CabalConfig
|
CabalConfig
|
||||||
, cabalConfigDependencies
|
, cabalConfigDependencies
|
||||||
@ -37,10 +38,12 @@ import Distribution.Simple.LocalBuildInfo (ComponentName)
|
|||||||
import System.FilePath ((</>))
|
import System.FilePath ((</>))
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
|
-- | 'Show'ed cabal 'LocalBuildInfo' string
|
||||||
type CabalConfig = String
|
type CabalConfig = String
|
||||||
|
|
||||||
-- | Get file containing 'LocalBuildInfo' data. If it doesn't exist run @cabal
|
-- | Get contents of the file containing 'LocalBuildInfo' data. If it doesn't
|
||||||
-- configure@ i.e. configure with default options like @cabal build@ would do.
|
-- exist run @cabal configure@ i.e. configure with default options like @cabal
|
||||||
|
-- build@ would do.
|
||||||
getConfig :: Cradle -> IO CabalConfig
|
getConfig :: Cradle -> IO CabalConfig
|
||||||
getConfig cradle =
|
getConfig cradle =
|
||||||
readFile path `E.catch` (\(E.SomeException _) -> configure >> readFile path)
|
readFile path `E.catch` (\(E.SomeException _) -> configure >> readFile path)
|
||||||
@ -55,10 +58,12 @@ getConfig cradle =
|
|||||||
configPath :: FilePath
|
configPath :: FilePath
|
||||||
configPath = localBuildInfoFile defaultDistPref
|
configPath = localBuildInfoFile defaultDistPref
|
||||||
|
|
||||||
|
-- | Get list of 'Package's needed by all components of the current package
|
||||||
cabalConfigDependencies :: Cradle -> PackageIdentifier -> IO [Package]
|
cabalConfigDependencies :: Cradle -> PackageIdentifier -> IO [Package]
|
||||||
cabalConfigDependencies cradle thisPkg =
|
cabalConfigDependencies cradle thisPkg =
|
||||||
configDependencies thisPkg <$> getConfig cradle
|
configDependencies thisPkg <$> getConfig cradle
|
||||||
|
|
||||||
|
-- | Extract list of depencenies for all components from 'CabalConfig'
|
||||||
configDependencies :: PackageIdentifier -> CabalConfig -> [Package]
|
configDependencies :: PackageIdentifier -> CabalConfig -> [Package]
|
||||||
configDependencies thisPkg config = map fromInstalledPackageId deps
|
configDependencies thisPkg config = map fromInstalledPackageId deps
|
||||||
where
|
where
|
||||||
@ -116,6 +121,8 @@ configDependencies thisPkg config = map fromInstalledPackageId deps
|
|||||||
Right x -> x
|
Right x -> x
|
||||||
Left msg -> error $ "reading config " ++ f ++ " failed ("++msg++")"
|
Left msg -> error $ "reading config " ++ f ++ " failed ("++msg++")"
|
||||||
|
|
||||||
|
-- | Find @field@ in 'CabalConfig'. Returns 'Left' containing a user readable
|
||||||
|
-- error message with lots of context on failure.
|
||||||
extractField :: CabalConfig -> String -> Either String String
|
extractField :: CabalConfig -> String -> Either String String
|
||||||
extractField config field =
|
extractField config field =
|
||||||
case extractParens <$> find (field `isPrefixOf`) (tails config) of
|
case extractParens <$> find (field `isPrefixOf`) (tails config) of
|
||||||
|
@ -49,7 +49,6 @@ import Language.Haskell.GhcMod.Types
|
|||||||
import Language.Haskell.GhcMod.Cradle
|
import Language.Haskell.GhcMod.Cradle
|
||||||
import Language.Haskell.GhcMod.DynFlags
|
import Language.Haskell.GhcMod.DynFlags
|
||||||
import Language.Haskell.GhcMod.GhcPkg
|
import Language.Haskell.GhcMod.GhcPkg
|
||||||
import Language.Haskell.GhcMod.GHCChoice
|
|
||||||
import Language.Haskell.GhcMod.CabalApi
|
import Language.Haskell.GhcMod.CabalApi
|
||||||
import qualified Language.Haskell.GhcMod.Gap as Gap
|
import qualified Language.Haskell.GhcMod.Gap as Gap
|
||||||
|
|
||||||
@ -200,7 +199,7 @@ initializeFlagsWithCradle :: GhcMonad m
|
|||||||
-> Cradle
|
-> Cradle
|
||||||
-> m ()
|
-> m ()
|
||||||
initializeFlagsWithCradle opt c
|
initializeFlagsWithCradle opt c
|
||||||
| cabal = withCabal |||> withSandbox
|
| cabal = withCabal
|
||||||
| otherwise = withSandbox
|
| otherwise = withSandbox
|
||||||
where
|
where
|
||||||
mCradleFile = cradleCabalFile c
|
mCradleFile = cradleCabalFile c
|
||||||
|
@ -1,6 +1,9 @@
|
|||||||
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
module MonadSpec where
|
module MonadSpec where
|
||||||
|
|
||||||
import Test.Hspec
|
import Test.Hspec
|
||||||
|
import Dir
|
||||||
|
import Control.Applicative
|
||||||
import Control.Monad.Error.Class
|
import Control.Monad.Error.Class
|
||||||
import Language.Haskell.GhcMod.Types
|
import Language.Haskell.GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Monad
|
import Language.Haskell.GhcMod.Monad
|
||||||
@ -17,3 +20,8 @@ spec = do
|
|||||||
return "hello"
|
return "hello"
|
||||||
`catchError` (const $ fail "oh noes")
|
`catchError` (const $ fail "oh noes")
|
||||||
a `shouldBe` (Left $ GMEString "oh noes")
|
a `shouldBe` (Left $ GMEString "oh noes")
|
||||||
|
|
||||||
|
describe "runGhcModT" $
|
||||||
|
it "complains if the cabal file fails to parse while a sandbox is present" $ withDirectory_ "test/data/broken-cabal" $ do
|
||||||
|
(a,_) <- runGhcModT defaultOptions (gmCradle <$> ask)
|
||||||
|
a `shouldSatisfy` (\(Left _) -> True)
|
||||||
|
BIN
test/data/broken-cabal/.cabal-sandbox/packages/00-index.tar
Normal file
BIN
test/data/broken-cabal/.cabal-sandbox/packages/00-index.tar
Normal file
Binary file not shown.
25
test/data/broken-cabal/cabal.sandbox.config.in
Normal file
25
test/data/broken-cabal/cabal.sandbox.config.in
Normal file
@ -0,0 +1,25 @@
|
|||||||
|
-- This is a Cabal package environment file.
|
||||||
|
-- THIS FILE IS AUTO-GENERATED. DO NOT EDIT DIRECTLY.
|
||||||
|
-- Please create a 'cabal.config' file in the same directory
|
||||||
|
-- if you want to change the default settings for this sandbox.
|
||||||
|
|
||||||
|
|
||||||
|
local-repo: @CWD@/test/data/broken-cabal/.cabal-sandbox/packages
|
||||||
|
logs-dir: @CWD@/test/data/broken-cabal/.cabal-sandbox/logs
|
||||||
|
world-file: @CWD@/test/data/broken-cabal/.cabal-sandbox/world
|
||||||
|
user-install: False
|
||||||
|
package-db: @CWD@/test/data/broken-cabal/.cabal-sandbox/x86_64-linux-ghc-7.8.3-packages.conf.d
|
||||||
|
build-summary: @CWD@/test/data/broken-cabal/.cabal-sandbox/logs/build.log
|
||||||
|
|
||||||
|
install-dirs
|
||||||
|
prefix: @CWD@/test/data/broken-cabal/.cabal-sandbox
|
||||||
|
bindir: $prefix/bin
|
||||||
|
libdir: $prefix/lib
|
||||||
|
libsubdir: $arch-$os-$compiler/$pkgid
|
||||||
|
libexecdir: $prefix/libexec
|
||||||
|
datadir: $prefix/share
|
||||||
|
datasubdir: $arch-$os-$compiler/$pkgid
|
||||||
|
docdir: $datadir/doc/$arch-$os-$compiler/$pkgid
|
||||||
|
htmldir: $docdir/html
|
||||||
|
haddockdir: $htmldir
|
||||||
|
sysconfdir: $prefix/etc
|
Loading…
Reference in New Issue
Block a user