removing warnings from spec.
This commit is contained in:
parent
190dc2ac51
commit
1e1505c535
@ -162,6 +162,7 @@ Test-Suite spec
|
||||
Default-Extensions: ConstraintKinds, FlexibleContexts
|
||||
Main-Is: Main.hs
|
||||
Hs-Source-Dirs: test, .
|
||||
Ghc-Options: -Wall
|
||||
Type: exitcode-stdio-1.0
|
||||
Other-Modules: Dir
|
||||
Spec
|
||||
|
@ -2,7 +2,6 @@ module BrowseSpec where
|
||||
|
||||
import Control.Applicative
|
||||
import Language.Haskell.GhcMod
|
||||
import Language.Haskell.GhcMod.Cradle
|
||||
import Test.Hspec
|
||||
|
||||
import TestUtils
|
||||
@ -22,7 +21,6 @@ spec = do
|
||||
syms `shouldContain` ["either :: (a -> c) -> (b -> c) -> Either a b -> c"]
|
||||
|
||||
it "contains type constructors (e.g. `Left') including their type signature" $ do
|
||||
cradle <- findCradle
|
||||
syms <- run defaultOptions { detailed = True}
|
||||
$ lines <$> browse "Data.Either"
|
||||
syms `shouldContain` ["Left :: a -> Either a b"]
|
||||
|
@ -3,7 +3,6 @@
|
||||
module CabalApiSpec where
|
||||
|
||||
import Control.Applicative
|
||||
import Control.Exception
|
||||
import Data.Maybe
|
||||
import Language.Haskell.GhcMod.CabalApi
|
||||
import Language.Haskell.GhcMod.Cradle
|
||||
@ -32,9 +31,9 @@ spec = do
|
||||
it "gets necessary CompilerOptions" $ do
|
||||
cwd <- getCurrentDirectory
|
||||
withDirectory "test/data/subdir1/subdir2" $ \dir -> do
|
||||
cradle <- findCradle
|
||||
pkgDesc <- runD $ parseCabalFile $ fromJust $ cradleCabalFile cradle
|
||||
res <- runD $ getCompilerOptions [] cradle pkgDesc
|
||||
crdl <- findCradle
|
||||
pkgDesc <- runD $ parseCabalFile $ fromJust $ cradleCabalFile crdl
|
||||
res <- runD $ getCompilerOptions [] crdl pkgDesc
|
||||
let res' = res {
|
||||
ghcOptions = ghcOptions res
|
||||
, includeDirs = map (toRelativeDir dir) (includeDirs res)
|
||||
|
@ -1,12 +1,7 @@
|
||||
module FindSpec where
|
||||
|
||||
import Control.Applicative ((<$>))
|
||||
import Data.List (isPrefixOf)
|
||||
import Language.Haskell.GhcMod.Find
|
||||
import Test.Hspec
|
||||
import TestUtils
|
||||
|
||||
import qualified Data.Map
|
||||
|
||||
spec :: Spec
|
||||
spec = do
|
||||
|
@ -1,12 +1,10 @@
|
||||
module GhcApiSpec where
|
||||
|
||||
import Control.Applicative
|
||||
import Control.Monad
|
||||
import Data.List (sort)
|
||||
import Language.Haskell.GhcMod.GHCApi
|
||||
import Test.Hspec
|
||||
import TestUtils
|
||||
import CoreMonad (liftIO)
|
||||
|
||||
import Dir
|
||||
|
||||
|
@ -2,7 +2,6 @@
|
||||
module GhcPkgSpec where
|
||||
|
||||
import Language.Haskell.GhcMod.GhcPkg
|
||||
import Language.Haskell.GhcMod.Types
|
||||
|
||||
import System.Directory
|
||||
import System.FilePath ((</>))
|
||||
|
@ -9,5 +9,5 @@ spec :: Spec
|
||||
spec = do
|
||||
describe "modules" $ do
|
||||
it "contains at least `Data.Map'" $ do
|
||||
modules <- runD $ lines <$> modules
|
||||
modules `shouldContain` ["Data.Map"]
|
||||
mdls <- runD $ lines <$> modules
|
||||
mdls `shouldContain` ["Data.Map"]
|
||||
|
19
test/Main.hs
19
test/Main.hs
@ -2,20 +2,21 @@
|
||||
import Spec
|
||||
import Dir
|
||||
|
||||
import Test.Hspec
|
||||
import System.Process
|
||||
|
||||
import Language.Haskell.GhcMod (debugInfo, defaultOptions, findCradle)
|
||||
import Control.Exception as E
|
||||
import Control.Monad (void)
|
||||
import Language.Haskell.GhcMod (debugInfo)
|
||||
import System.Process
|
||||
import Test.Hspec
|
||||
import TestUtils
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
let sandboxes = [ "test/data", "test/data/check-packageid"
|
||||
, "test/data/duplicate-pkgver/"
|
||||
, "test/data/broken-cabal/"
|
||||
]
|
||||
genSandboxCfg dir = withDirectory dir $ \cwd -> do
|
||||
system ("sed 's|@CWD@|" ++ cwd ++ "|g' cabal.sandbox.config.in > cabal.sandbox.config")
|
||||
genSandboxCfg dir = withDirectory dir $ \cwdir -> do
|
||||
system ("sed 's|@CWD@|" ++ cwdir ++ "|g' cabal.sandbox.config.in > cabal.sandbox.config")
|
||||
pkgDirs =
|
||||
[ "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"
|
||||
@ -23,10 +24,10 @@ main = do
|
||||
genGhcPkgCache dir = system $ "ghc-pkg recache --force -f" ++ dir
|
||||
genSandboxCfg `mapM_` sandboxes
|
||||
genGhcPkgCache `mapM_` pkgDirs
|
||||
system "find test -name setup-config -name ghc-mod.cache -exec rm {} \\;"
|
||||
system "cabal --version"
|
||||
void $ system "find test -name setup-config -name ghc-mod.cache -exec rm {} \\;"
|
||||
void $ system "cabal --version"
|
||||
putStrLn $ "ghc-mod was built with Cabal version " ++ VERSION_Cabal
|
||||
system "ghc --version"
|
||||
void $ system "ghc --version"
|
||||
|
||||
(putStrLn =<< runD debugInfo)
|
||||
`E.catch` (\(_ :: E.SomeException) -> return () )
|
||||
|
@ -6,18 +6,15 @@ import Dir
|
||||
import TestUtils
|
||||
import Control.Applicative
|
||||
import Control.Monad.Error.Class
|
||||
import Language.Haskell.GhcMod.Types
|
||||
import Language.Haskell.GhcMod.Monad
|
||||
import Language.Haskell.GhcMod.Find
|
||||
|
||||
spec :: Spec
|
||||
spec = do
|
||||
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
|
||||
(a, w)
|
||||
(a, _)
|
||||
<- runGhcModT defaultOptions $
|
||||
do
|
||||
Just a <- return Nothing
|
||||
Just _ <- return Nothing
|
||||
return "hello"
|
||||
`catchError` (const $ fail "oh noes")
|
||||
a `shouldBe` (Left $ GMEString "oh noes")
|
||||
|
@ -1,7 +1,6 @@
|
||||
module UtilsSpec where
|
||||
|
||||
import Language.Haskell.GhcMod.Utils
|
||||
import System.IO.Error
|
||||
import Control.Exception
|
||||
import TestUtils
|
||||
import Test.Hspec
|
||||
|
Loading…
Reference in New Issue
Block a user