fixing tests.

This commit is contained in:
Kazu Yamamoto 2013-09-21 18:37:33 +09:00
parent 78e841547a
commit a94b1a3b5a
6 changed files with 33 additions and 21 deletions

View File

@ -1,6 +1,10 @@
{-# LANGUAGE BangPatterns #-}
module Language.Haskell.GhcMod.Cradle (findCradle, getPackageDbDir) where
module Language.Haskell.GhcMod.Cradle (
findCradle
, findCradleWithoutSandbox
, getPackageDbDir
) where
import Data.Char (isSpace)
import Control.Applicative ((<$>))
@ -41,6 +45,12 @@ findCradle' wdir = do
, cradlePackageDbOpts = pkgDbOpts
}
-- Just for testing
findCradleWithoutSandbox :: IO Cradle
findCradleWithoutSandbox = do
cradle <- findCradle
return cradle { cradlePackageDbOpts = [] }
----------------------------------------------------------------
cabalSuffix :: String

View File

@ -25,10 +25,10 @@ spec = do
pkgDesc <- parseCabalFile $ fromJust $ cradleCabalFile cradle
res <- getCompilerOptions [] cradle pkgDesc
let res' = res {
ghcOptions = map (toRelativeDir dir) (ghcOptions res)
ghcOptions = ghcOptions res
, includeDirs = map (toRelativeDir dir) (includeDirs res)
}
res' `shouldBe` CompilerOptions {ghcOptions = ["-no-user-package-db","-package-db","test/data/.cabal-sandbox/i386-osx-ghc-7.6.3-packages.conf.d","-XHaskell98"], includeDirs = ["test/data","test/data/dist/build","test/data/dist/build/autogen","test/data/subdir1/subdir2","test/data/test"], depPackages = ["Cabal","base","template-haskell"]}
res' `shouldBe` CompilerOptions {ghcOptions = ["-no-user-package-db","-package-db","/home/me/work/ghc-mod/test/data/.cabal-sandbox/i386-osx-ghc-7.6.3-packages.conf.d","-XHaskell98"], includeDirs = ["test/data","test/data/dist/build","test/data/dist/build/autogen","test/data/subdir1/subdir2","test/data/test"], depPackages = ["Cabal","base","template-haskell"]}
describe "cabalDependPackages" $ do
it "extracts dependent packages" $ do

View File

@ -2,6 +2,7 @@ module CheckSpec where
import Data.List (isSuffixOf, isInfixOf, isPrefixOf)
import Language.Haskell.GhcMod
import Language.Haskell.GhcMod.Cradle
import System.FilePath
import Test.Hspec
@ -12,24 +13,24 @@ spec = do
describe "checkSyntax" $ do
it "can check even if an executable depends on its library" $ do
withDirectory_ "test/data/ghc-mod-check" $ do
cradle <- findCradle
cradle <- findCradleWithoutSandbox
res <- checkSyntax defaultOptions cradle ["main.hs"]
res `shouldBe` "main.hs:5:1:Warning: Top-level binding with no type signature: main :: IO ()\NUL\n"
it "can check even if a test module imports another test module located at different directory" $ do
withDirectory_ "test/data/check-test-subdir" $ do
cradle <- findCradle
cradle <- findCradleWithoutSandbox
res <- checkSyntax defaultOptions cradle ["test/Bar/Baz.hs"]
res `shouldSatisfy` (("test" </> "Foo.hs:3:1:Warning: Top-level binding with no type signature: foo :: [Char]\NUL\n") `isSuffixOf`)
it "can detect mutually imported modules" $ do
withDirectory_ "test/data" $ do
cradle <- findCradle
cradle <- findCradleWithoutSandbox
res <- checkSyntax defaultOptions cradle ["Mutual1.hs"]
res `shouldSatisfy` ("Module imports form a cycle" `isInfixOf`)
it "can check a module using QuasiQuotes" $ do
withDirectory_ "test/data" $ do
cradle <- findCradle
cradle <- findCradleWithoutSandbox
res <- checkSyntax defaultOptions cradle ["Baz.hs"]
res `shouldSatisfy` ("Baz.hs:5:1:Warning:" `isPrefixOf`)

View File

@ -29,7 +29,7 @@ spec = do
cradleCurrentDir = "test" </> "data" </> "subdir1" </> "subdir2"
, cradleCabalDir = Just ("test" </> "data")
, cradleCabalFile = Just ("test" </> "data" </> "cabalapi.cabal")
, cradlePackageDbOpts = ["-no-user-package-db", "-package-db", "test" </> "data" </> ".cabal-sandbox" </> "i386-osx-ghc-7.6.3-packages.conf.d"]
, cradlePackageDbOpts = ["-no-user-package-db", "-package-db", "test" </> "data" </> ".cabal-sandbox" </> "/home/me/work/ghc-mod/test/data/.cabal-sandbox/i386-osx-ghc-7.6.3-packages.conf.d"]
}
it "works even if a sandbox config file is broken" $ do
withDirectory "test/data/broken-sandbox" $ \dir -> do
@ -44,7 +44,7 @@ spec = do
describe "getPackageDbDir" $ do
it "parses a config file and extracts package db" $ do
pkgDb <- getPackageDbDir "test/data/cabal.sandbox.config"
pkgDb `shouldBe` "/Users/kazu/work/ghc-mod/test/data/.cabal-sandbox/i386-osx-ghc-7.6.3-packages.conf.d"
pkgDb `shouldBe` "/home/me/work/ghc-mod/test/data/.cabal-sandbox/i386-osx-ghc-7.6.3-packages.conf.d"
it "throws an error if a config file is broken" $ do
getPackageDbDir "test/data/bad.config" `shouldThrow` anyException

View File

@ -2,6 +2,7 @@ module InfoSpec where
import Data.List (isPrefixOf)
import Language.Haskell.GhcMod
import Language.Haskell.GhcMod.Cradle
import System.Exit
import System.Process
import Test.Hspec
@ -13,38 +14,38 @@ spec = do
describe "typeExpr" $ do
it "shows types of the expression and its outers" $ do
withDirectory_ "test/data/ghc-mod-check" $ do
cradle <- findCradle
cradle <- findCradleWithoutSandbox
res <- typeExpr defaultOptions cradle "Data/Foo.hs" "Data.Foo" 9 5
res `shouldBe` "9 5 11 40 \"Int -> a -> a -> a\"\n7 1 11 40 \"Int -> Integer\"\n"
it "works with a module using TemplateHaskell" $ do
withDirectory_ "test/data" $ do
cradle <- findCradle
cradle <- findCradleWithoutSandbox
res <- typeExpr defaultOptions cradle "Bar.hs" "Bar" 5 1
res `shouldBe` unlines ["5 1 5 20 \"[Char]\""]
it "works with a module that imports another module using TemplateHaskell" $ do
withDirectory_ "test/data" $ do
cradle <- findCradle
cradle <- findCradleWithoutSandbox
res <- typeExpr defaultOptions cradle "Main.hs" "Main" 3 8
res `shouldBe` unlines ["3 8 3 16 \"String -> IO ()\"", "3 8 3 20 \"IO ()\"", "3 1 3 20 \"IO ()\""]
describe "infoExpr" $ do
it "works for non-export functions" $ do
withDirectory_ "test/data" $ do
cradle <- findCradle
cradle <- findCradleWithoutSandbox
res <- infoExpr defaultOptions cradle "Info.hs" "Info" "fib"
res `shouldSatisfy` ("fib :: Int -> Int" `isPrefixOf`)
it "works with a module using TemplateHaskell" $ do
withDirectory_ "test/data" $ do
cradle <- findCradle
cradle <- findCradleWithoutSandbox
res <- infoExpr defaultOptions cradle "Bar.hs" "Bar" "foo"
res `shouldSatisfy` ("foo :: ExpQ" `isPrefixOf`)
it "works with a module that imports another module using TemplateHaskell" $ do
withDirectory_ "test/data" $ do
cradle <- findCradle
cradle <- findCradleWithoutSandbox
res <- infoExpr defaultOptions cradle "Main.hs" "Main" "bar"
res `shouldSatisfy` ("bar :: [Char]" `isPrefixOf`)

View File

@ -4,15 +4,15 @@
-- if you want to change the default settings for this sandbox.
local-repo: /Users/kazu/work/ghc-mod/test/data/.cabal-sandbox/packages
logs-dir: /Users/kazu/work/ghc-mod/test/data/.cabal-sandbox/logs
world-file: /Users/kazu/work/ghc-mod/test/data/.cabal-sandbox/world
local-repo: /home/me/work/ghc-mod/test/data/.cabal-sandbox/packages
logs-dir: /home/me/work/ghc-mod/test/data/.cabal-sandbox/logs
world-file: /home/me/work/ghc-mod/test/data/.cabal-sandbox/world
user-install: False
package-db: /Users/kazu/work/ghc-mod/test/data/.cabal-sandbox/i386-osx-ghc-7.6.3-packages.conf.d
build-summary: /Users/kazu/work/ghc-mod/test/data/.cabal-sandbox/logs/build.log
package-db: /home/me/work/ghc-mod/test/data/.cabal-sandbox/i386-osx-ghc-7.6.3-packages.conf.d
build-summary: /home/me/work/ghc-mod/test/data/.cabal-sandbox/logs/build.log
install-dirs
prefix: /Users/kazu/work/ghc-mod/test/data/.cabal-sandbox
prefix: /home/me/work/ghc-mod/test/data/.cabal-sandbox
bindir: $prefix/bin
libdir: $prefix/lib
libsubdir: $arch-$os-$compiler/$pkgid