removing warnings from spec.

This commit is contained in:
Kazu Yamamoto 2014-08-20 12:14:27 +09:00
parent 190dc2ac51
commit 1e1505c535
10 changed files with 18 additions and 31 deletions

View File

@ -162,6 +162,7 @@ Test-Suite spec
Default-Extensions: ConstraintKinds, FlexibleContexts Default-Extensions: ConstraintKinds, FlexibleContexts
Main-Is: Main.hs Main-Is: Main.hs
Hs-Source-Dirs: test, . Hs-Source-Dirs: test, .
Ghc-Options: -Wall
Type: exitcode-stdio-1.0 Type: exitcode-stdio-1.0
Other-Modules: Dir Other-Modules: Dir
Spec Spec

View File

@ -2,7 +2,6 @@ module BrowseSpec where
import Control.Applicative import Control.Applicative
import Language.Haskell.GhcMod import Language.Haskell.GhcMod
import Language.Haskell.GhcMod.Cradle
import Test.Hspec import Test.Hspec
import TestUtils import TestUtils
@ -22,7 +21,6 @@ spec = do
syms `shouldContain` ["either :: (a -> c) -> (b -> c) -> Either a b -> c"] syms `shouldContain` ["either :: (a -> c) -> (b -> c) -> Either a b -> c"]
it "contains type constructors (e.g. `Left') including their type signature" $ do it "contains type constructors (e.g. `Left') including their type signature" $ do
cradle <- findCradle
syms <- run defaultOptions { detailed = True} syms <- run defaultOptions { detailed = True}
$ lines <$> browse "Data.Either" $ lines <$> browse "Data.Either"
syms `shouldContain` ["Left :: a -> Either a b"] syms `shouldContain` ["Left :: a -> Either a b"]

View File

@ -3,7 +3,6 @@
module CabalApiSpec where module CabalApiSpec where
import Control.Applicative import Control.Applicative
import Control.Exception
import Data.Maybe import Data.Maybe
import Language.Haskell.GhcMod.CabalApi import Language.Haskell.GhcMod.CabalApi
import Language.Haskell.GhcMod.Cradle import Language.Haskell.GhcMod.Cradle
@ -32,9 +31,9 @@ spec = do
it "gets necessary CompilerOptions" $ do it "gets necessary CompilerOptions" $ do
cwd <- getCurrentDirectory cwd <- getCurrentDirectory
withDirectory "test/data/subdir1/subdir2" $ \dir -> do withDirectory "test/data/subdir1/subdir2" $ \dir -> do
cradle <- findCradle crdl <- findCradle
pkgDesc <- runD $ parseCabalFile $ fromJust $ cradleCabalFile cradle pkgDesc <- runD $ parseCabalFile $ fromJust $ cradleCabalFile crdl
res <- runD $ getCompilerOptions [] cradle pkgDesc res <- runD $ getCompilerOptions [] crdl pkgDesc
let res' = res { let res' = res {
ghcOptions = ghcOptions res ghcOptions = ghcOptions res
, includeDirs = map (toRelativeDir dir) (includeDirs res) , includeDirs = map (toRelativeDir dir) (includeDirs res)

View File

@ -1,12 +1,7 @@
module FindSpec where module FindSpec where
import Control.Applicative ((<$>))
import Data.List (isPrefixOf)
import Language.Haskell.GhcMod.Find import Language.Haskell.GhcMod.Find
import Test.Hspec import Test.Hspec
import TestUtils
import qualified Data.Map
spec :: Spec spec :: Spec
spec = do spec = do

View File

@ -1,12 +1,10 @@
module GhcApiSpec where module GhcApiSpec where
import Control.Applicative import Control.Applicative
import Control.Monad
import Data.List (sort) import Data.List (sort)
import Language.Haskell.GhcMod.GHCApi import Language.Haskell.GhcMod.GHCApi
import Test.Hspec import Test.Hspec
import TestUtils import TestUtils
import CoreMonad (liftIO)
import Dir import Dir

View File

@ -2,7 +2,6 @@
module GhcPkgSpec where module GhcPkgSpec where
import Language.Haskell.GhcMod.GhcPkg import Language.Haskell.GhcMod.GhcPkg
import Language.Haskell.GhcMod.Types
import System.Directory import System.Directory
import System.FilePath ((</>)) import System.FilePath ((</>))

View File

@ -9,5 +9,5 @@ spec :: Spec
spec = do spec = do
describe "modules" $ do describe "modules" $ do
it "contains at least `Data.Map'" $ do it "contains at least `Data.Map'" $ do
modules <- runD $ lines <$> modules mdls <- runD $ lines <$> modules
modules `shouldContain` ["Data.Map"] mdls `shouldContain` ["Data.Map"]

View File

@ -2,20 +2,21 @@
import Spec import Spec
import Dir import Dir
import Test.Hspec
import System.Process
import Language.Haskell.GhcMod (debugInfo, defaultOptions, findCradle)
import Control.Exception as E import Control.Exception as E
import Control.Monad (void)
import Language.Haskell.GhcMod (debugInfo)
import System.Process
import Test.Hspec
import TestUtils import TestUtils
main :: IO ()
main = do main = do
let sandboxes = [ "test/data", "test/data/check-packageid" let sandboxes = [ "test/data", "test/data/check-packageid"
, "test/data/duplicate-pkgver/" , "test/data/duplicate-pkgver/"
, "test/data/broken-cabal/" , "test/data/broken-cabal/"
] ]
genSandboxCfg dir = withDirectory dir $ \cwd -> do genSandboxCfg dir = withDirectory dir $ \cwdir -> do
system ("sed 's|@CWD@|" ++ cwd ++ "|g' cabal.sandbox.config.in > cabal.sandbox.config") system ("sed 's|@CWD@|" ++ cwdir ++ "|g' cabal.sandbox.config.in > cabal.sandbox.config")
pkgDirs = pkgDirs =
[ "test/data/.cabal-sandbox/i386-osx-ghc-7.6.3-packages.conf.d" [ "test/data/.cabal-sandbox/i386-osx-ghc-7.6.3-packages.conf.d"
, "test/data/check-packageid/.cabal-sandbox/i386-osx-ghc-7.6.3-packages.conf.d" , "test/data/check-packageid/.cabal-sandbox/i386-osx-ghc-7.6.3-packages.conf.d"
@ -23,10 +24,10 @@ main = do
genGhcPkgCache dir = system $ "ghc-pkg recache --force -f" ++ dir genGhcPkgCache dir = system $ "ghc-pkg recache --force -f" ++ dir
genSandboxCfg `mapM_` sandboxes genSandboxCfg `mapM_` sandboxes
genGhcPkgCache `mapM_` pkgDirs genGhcPkgCache `mapM_` pkgDirs
system "find test -name setup-config -name ghc-mod.cache -exec rm {} \\;" void $ system "find test -name setup-config -name ghc-mod.cache -exec rm {} \\;"
system "cabal --version" void $ system "cabal --version"
putStrLn $ "ghc-mod was built with Cabal version " ++ VERSION_Cabal putStrLn $ "ghc-mod was built with Cabal version " ++ VERSION_Cabal
system "ghc --version" void $ system "ghc --version"
(putStrLn =<< runD debugInfo) (putStrLn =<< runD debugInfo)
`E.catch` (\(_ :: E.SomeException) -> return () ) `E.catch` (\(_ :: E.SomeException) -> return () )

View File

@ -6,18 +6,15 @@ import Dir
import TestUtils import TestUtils
import Control.Applicative import Control.Applicative
import Control.Monad.Error.Class import Control.Monad.Error.Class
import Language.Haskell.GhcMod.Types
import Language.Haskell.GhcMod.Monad
import Language.Haskell.GhcMod.Find
spec :: Spec spec :: Spec
spec = do spec = do
describe "When using GhcModT in a do block" $ describe "When using GhcModT in a do block" $
it "a pattern match failure causes a call to `fail` on ErrorT in the monad stack" $ do it "a pattern match failure causes a call to `fail` on ErrorT in the monad stack" $ do
(a, w) (a, _)
<- runGhcModT defaultOptions $ <- runGhcModT defaultOptions $
do do
Just a <- return Nothing Just _ <- return Nothing
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")

View File

@ -1,7 +1,6 @@
module UtilsSpec where module UtilsSpec where
import Language.Haskell.GhcMod.Utils import Language.Haskell.GhcMod.Utils
import System.IO.Error
import Control.Exception import Control.Exception
import TestUtils import TestUtils
import Test.Hspec import Test.Hspec