removing shouldContain since hspec provides it!

This commit is contained in:
Kazu Yamamoto 2013-09-03 11:44:59 +09:00
parent 159c181323
commit 1b862ca107
7 changed files with 8 additions and 18 deletions

View File

@ -116,7 +116,7 @@ Test-Suite spec
, syb
, time
, transformers
, hspec
, hspec >= 1.7.1
Source-Repository head
Type: git

View File

@ -1,7 +1,6 @@
module BrowseSpec where
import Control.Applicative
import Expectation
import Language.Haskell.GhcMod
import Test.Hspec
@ -10,13 +9,13 @@ spec = do
describe "browseModule" $ do
it "lists up symbols in the module" $ do
syms <- lines <$> browseModule defaultOptions "Data.Map"
syms `shouldContain` "differenceWithKey"
syms `shouldContain` ["differenceWithKey"]
describe "browseModule -d" $ do
it "lists up symbols with type info in the module" $ do
syms <- lines <$> browseModule defaultOptions { detailed = True } "Data.Either"
syms `shouldContain` "either :: (a -> c) -> (b -> c) -> Either a b -> c"
syms `shouldContain` ["either :: (a -> c) -> (b -> c) -> Either a b -> c"]
it "lists up data constructors with type info in the module" $ do
syms <- lines <$> browseModule defaultOptions { detailed = True} "Data.Either"
syms `shouldContain` "Left :: a -> Either a b"
syms `shouldContain` ["Left :: a -> Either a b"]

View File

@ -9,7 +9,7 @@ checkFast file ans = withDirectory_ "test/data" $ do
(strVer,_) <- getGHCVersion
cradle <- findCradle Nothing strVer
res <- debugInfo defaultOptions cradle strVer file
lines res `shouldContain` ans
lines res `shouldContain` [ans]
spec :: Spec
spec = do

View File

@ -1,14 +1,8 @@
module Expectation where
import Test.Hspec
import System.Directory
import Control.Exception as E
shouldContain :: Eq a => [a] -> a -> Expectation
shouldContain containers element = do
let res = element `elem` containers
res `shouldBe` True
withDirectory_ :: FilePath -> IO a -> IO a
withDirectory_ dir action = bracket getCurrentDirectory
setCurrentDirectory

View File

@ -1,7 +1,6 @@
module FlagSpec where
import Control.Applicative
import Expectation
import Language.Haskell.GhcMod
import Test.Hspec
@ -10,4 +9,4 @@ spec = do
describe "listFlags" $ do
it "lists up GHC flags" $ do
flags <- lines <$> listFlags defaultOptions
flags `shouldContain` "-fno-warn-orphans"
flags `shouldContain` ["-fno-warn-orphans"]

View File

@ -1,7 +1,6 @@
module LangSpec where
import Control.Applicative
import Expectation
import Language.Haskell.GhcMod
import Test.Hspec
@ -10,4 +9,4 @@ spec = do
describe "listLanguages" $ do
it "lists up language extensions" $ do
exts <- lines <$> listLanguages defaultOptions
exts `shouldContain` "OverloadedStrings"
exts `shouldContain` ["OverloadedStrings"]

View File

@ -1,7 +1,6 @@
module ListSpec where
import Control.Applicative
import Expectation
import Language.Haskell.GhcMod
import Test.Hspec
@ -10,4 +9,4 @@ spec = do
describe "listModules" $ do
it "lists up module names" $ do
modules <- lines <$> listModules defaultOptions
modules `shouldContain` "Data.Map"
modules `shouldContain` ["Data.Map"]