module name change.
This commit is contained in:
parent
1b862ca107
commit
955223a2a8
@ -90,7 +90,7 @@ Test-Suite spec
|
||||
Main-Is: Spec.hs
|
||||
Hs-Source-Dirs: test, .
|
||||
Type: exitcode-stdio-1.0
|
||||
Other-Modules: Expectation
|
||||
Other-Modules: Dir
|
||||
BrowseSpec
|
||||
CabalApiSpec
|
||||
CheckSpec
|
||||
|
@ -1,11 +1,12 @@
|
||||
module CheckSpec where
|
||||
|
||||
import Data.List (isSuffixOf, isInfixOf, isPrefixOf)
|
||||
import Expectation
|
||||
import Language.Haskell.GhcMod
|
||||
import System.FilePath
|
||||
import Test.Hspec
|
||||
|
||||
import Dir
|
||||
|
||||
spec :: Spec
|
||||
spec = do
|
||||
describe "checkSyntax" $ do
|
||||
|
@ -2,12 +2,13 @@ module CradleSpec where
|
||||
|
||||
import Control.Applicative
|
||||
import Data.List (isPrefixOf)
|
||||
import Expectation
|
||||
import Language.Haskell.GhcMod
|
||||
import System.Directory (canonicalizePath)
|
||||
import System.FilePath (addTrailingPathSeparator, (</>))
|
||||
import Test.Hspec
|
||||
|
||||
import Dir
|
||||
|
||||
spec :: Spec
|
||||
spec = do
|
||||
describe "findCradle" $ do
|
||||
|
@ -1,9 +1,10 @@
|
||||
module DebugSpec where
|
||||
|
||||
import Expectation
|
||||
import Language.Haskell.GhcMod
|
||||
import Test.Hspec
|
||||
|
||||
import Dir
|
||||
|
||||
checkFast :: String -> String -> IO ()
|
||||
checkFast file ans = withDirectory_ "test/data" $ do
|
||||
(strVer,_) <- getGHCVersion
|
||||
|
@ -1,4 +1,4 @@
|
||||
module Expectation where
|
||||
module Dir where
|
||||
|
||||
import System.Directory
|
||||
import Control.Exception as E
|
@ -1,12 +1,13 @@
|
||||
module InfoSpec where
|
||||
|
||||
import Data.List (isPrefixOf)
|
||||
import Expectation
|
||||
import Language.Haskell.GhcMod
|
||||
import System.Exit
|
||||
import System.Process
|
||||
import Test.Hspec
|
||||
|
||||
import Dir
|
||||
|
||||
spec :: Spec
|
||||
spec = do
|
||||
describe "typeExpr" $ do
|
||||
|
Loading…
Reference in New Issue
Block a user