Re-enable cabal-helper tests

This commit is contained in:
Daniel Gröber 2015-08-07 04:13:12 +02:00
parent 9dc7a9375e
commit f85327a1b6
1 changed files with 38 additions and 33 deletions

View File

@ -2,16 +2,17 @@ module CabalHelperSpec where
import Control.Arrow import Control.Arrow
import Control.Applicative import Control.Applicative
-- import Language.Haskell.GhcMod.CabalHelper import Distribution.Helper
-- import Language.Haskell.GhcMod.PathsAndFiles import Language.Haskell.GhcMod.CabalHelper
import Language.Haskell.GhcMod.PathsAndFiles
import Language.Haskell.GhcMod.Error import Language.Haskell.GhcMod.Error
import Test.Hspec import Test.Hspec
-- import System.Directory import System.Directory
-- import System.FilePath import System.FilePath
-- import System.Process (readProcess) import System.Process (readProcess)
-- import Dir import Dir
-- import TestUtils import TestUtils
import Data.List import Data.List
import Config (cProjectVersionInt) import Config (cProjectVersionInt)
@ -36,35 +37,39 @@ idirOpts :: [(c, [String])] -> [(c, [String])]
idirOpts = map (second $ map (drop 2) . filter ("-i"`isPrefixOf`)) idirOpts = map (second $ map (drop 2) . filter ("-i"`isPrefixOf`))
spec :: Spec spec :: Spec
spec = do return () spec = do
-- describe "getGhcOptions" $ do describe "getComponents" $ do
-- it "throws an exception if the cabal file is broken" $ do it "throws an exception if the cabal file is broken" $ do
-- let tdir = "test/data/broken-caba" let tdir = "test/data/broken-cabal"
-- runD' tdir getGhcOptions `shouldThrow` anyIOException runD' tdir getComponents `shouldThrow` anyIOException
-- it "handles sandboxes correctly" $ do it "handles sandboxes correctly" $ do
-- let tdir = "test/data/cabal-project" let tdir = "test/data/cabal-project"
-- cwd <- getCurrentDirectory cwd <- getCurrentDirectory
-- opts <- runD' tdir getGhcOptions -- TODO: ChSetupHsName should also have sandbox stuff, see related
-- comment in cabal-helper
opts <- map gmcGhcOpts . filter ((/= ChSetupHsName) . gmcName) <$> runD' tdir getComponents
-- if ghcVersion < 706 print opts
-- then forM_ opts (\(_, o) -> o `shouldContain` ["-no-user-package-conf","-package-conf", cwd </> "test/data/cabal-project/.cabal-sandbox/"++ghcSandboxPkgDbDir])
-- else forM_ opts (\(_, o) -> o `shouldContain` ["-no-user-package-db","-package-db",cwd </> "test/data/cabal-project/.cabal-sandbox/"++ghcSandboxPkgDbDir])
-- it "extracts build dependencies" $ do if ghcVersion < 706
-- let tdir = "test/data/cabal-project" then forM_ opts (\o -> o `shouldContain` ["-no-user-package-conf","-package-conf", cwd </> "test/data/cabal-project/.cabal-sandbox/"++ghcSandboxPkgDbDir])
-- opts <- runD' tdir getGhcOptions else forM_ opts (\o -> o `shouldContain` ["-no-user-package-db","-package-db",cwd </> "test/data/cabal-project/.cabal-sandbox/"++ghcSandboxPkgDbDir])
-- let ghcOpts = snd $ head opts
-- pkgs = pkgOptions ghcOpts
-- pkgs `shouldBe` ["Cabal","base","template-haskell"]
-- it "uses non default flags" $ do it "extracts build dependencies" $ do
-- let tdir = "test/data/cabal-flags" let tdir = "test/data/cabal-project"
-- _ <- withDirectory_ tdir $ opts <- map gmcGhcOpts <$> runD' tdir getComponents
-- readProcess "cabal" ["configure", "-ftest-flag"] "" let ghcOpts = head opts
pkgs = pkgOptions ghcOpts
pkgs `shouldBe` ["Cabal","base","template-haskell"]
-- opts <- runD' tdir getGhcOptions it "uses non default flags" $ do
-- let ghcOpts = snd $ head opts let tdir = "test/data/cabal-flags"
-- pkgs = pkgOptions ghcOpts _ <- withDirectory_ tdir $
-- pkgs `shouldBe` ["Cabal","base"] readProcess "cabal" ["configure", "-ftest-flag"] ""
opts <- map gmcGhcOpts <$> runD' tdir getComponents
let ghcOpts = head opts
pkgs = pkgOptions ghcOpts
pkgs `shouldBe` ["Cabal","base"]