Fix doc in non-cabal projects
..man those non-cabal projects are really getting me down. Who uses those anwayways ;)
This commit is contained in:
@@ -91,6 +91,6 @@ spec = do
|
||||
(s, s') <- runD $ do
|
||||
Just stack <- getCustomPkgDbStack
|
||||
withCabal $ do
|
||||
stack' <- getPackageDbStack'
|
||||
stack' <- getCabalPackageDbStack
|
||||
return (stack, stack')
|
||||
s' `shouldBe` s
|
||||
|
||||
30
test/GhcPkgSpec.hs
Normal file
30
test/GhcPkgSpec.hs
Normal file
@@ -0,0 +1,30 @@
|
||||
module GhcPkgSpec where
|
||||
|
||||
import Control.Arrow
|
||||
import Control.Applicative
|
||||
import Distribution.Helper
|
||||
import Language.Haskell.GhcMod.GhcPkg
|
||||
import Language.Haskell.GhcMod.PathsAndFiles
|
||||
import Language.Haskell.GhcMod.CabalHelper
|
||||
import Language.Haskell.GhcMod.Error
|
||||
import Test.Hspec
|
||||
import System.Directory
|
||||
import System.FilePath
|
||||
import System.Process (readProcess, system)
|
||||
|
||||
import Dir
|
||||
import TestUtils
|
||||
import Data.List
|
||||
|
||||
spec :: Spec
|
||||
spec = do
|
||||
describe "getPackageDbStack'" $ do
|
||||
it "fixes out of sync custom pkg-db stack" $ do
|
||||
withDirectory_ "test/data/custom-cradle" $ do
|
||||
_ <- system "cabal configure"
|
||||
(s, s') <- runD $ do
|
||||
Just stack <- getCustomPkgDbStack
|
||||
withCabal $ do
|
||||
stack' <- getPackageDbStack
|
||||
return (stack, stack')
|
||||
s' `shouldBe` s
|
||||
Reference in New Issue
Block a user