Gather all hs-source-dirs to check test modules in sub-directories

This commit is contained in:
eagletmt 2013-03-15 17:30:21 +09:00
parent 8d7b0d365b
commit 24ada2abeb
8 changed files with 51 additions and 1 deletions

View File

@ -5,6 +5,7 @@ module CabalApi (
, cabalParseFile
, cabalBuildInfo
, cabalAllDependPackages
, cabalAllSourceDirs
, getGHCVersion
) where
@ -43,7 +44,7 @@ cookInfo ghcOptions cradle cabal = (gopts,idirs,depPkgs)
Just cfile = cradleCabalFile cradle
binfo = cabalBuildInfo cabal
gopts = getGHCOptions ghcOptions binfo
idirs = includeDirectroies cdir owdir $ hsSourceDirs binfo
idirs = includeDirectroies cdir owdir $ cabalAllSourceDirs cabal
depPkgs = removeMe cfile $ cabalAllDependPackages cabal
removeMe :: FilePath -> [String] -> [String]
@ -79,6 +80,11 @@ cabalBuildInfo pd = fromJust $ fromLibrary pd <|> fromExecutable pd
----------------------------------------------------------------
cabalAllSourceDirs :: GenericPackageDescription -> [FilePath]
cabalAllSourceDirs = fromPackageDescription (f libBuildInfo) (f buildInfo) (f testBuildInfo) (f benchmarkBuildInfo)
where
f getBuildInfo = concatMap (hsSourceDirs . getBuildInfo . condTreeData)
cabalAllDependPackages :: GenericPackageDescription -> [Package]
cabalAllDependPackages pd = uniqueAndSort pkgs
where

View File

@ -11,6 +11,11 @@ spec = do
pkgs <- cabalAllDependPackages <$> cabalParseFile "test/data/cabalapi.cabal"
pkgs `shouldBe` ["Cabal","base","template-haskell"]
describe "cabalAllSourceDirs" $ do
it "extracts all hs-source-dirs" $ do
dirs <- cabalAllSourceDirs <$> cabalParseFile "test/data/check-test-subdir/check-test-subdir.cabal"
dirs `shouldBe` ["src", "test"]
describe "cabalBuildInfo" $ do
it "extracts build info" $ do
info <- cabalBuildInfo <$> cabalParseFile "test/data/cabalapi.cabal"

View File

@ -3,6 +3,7 @@ module CheckSpec where
import CabalApi
import Check
import Cradle
import Data.List (isSuffixOf)
import Expectation
import Test.Hspec
import Types
@ -16,3 +17,9 @@ spec = do
cradle <- findCradle Nothing strVer
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 <- getGHCVersion >>= findCradle Nothing . fst
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`)

View File

@ -0,0 +1,15 @@
name: check-test-subdir
version: 0.1.0
build-type: Simple
cabal-version: >= 1.8
library
build-depends: base == 4.*
hs-source-dirs: src
exposed-modules: Check.Test.Subdir
test-suite test
type: exitcode-stdio-1.0
build-depends: base == 4.*
hs-source-dirs: test
main-is: Main.hs

View File

@ -0,0 +1,4 @@
module Check.Test.Subdir (subdir) where
subdir :: String
subdir = "subdir"

View File

@ -0,0 +1,5 @@
module Bar.Baz (baz) where
import Foo (foo)
baz :: String
baz = unwords [foo, "baz"]

View File

@ -0,0 +1,3 @@
module Foo (foo) where
foo = "foo"

View File

@ -0,0 +1,5 @@
module Main where
import Bar.Baz (baz)
main :: IO ()
main = putStrLn baz