more tests.
This commit is contained in:
parent
1212040e3b
commit
a491927ef6
@ -4,15 +4,29 @@ module CabalApiSpec where
|
|||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Control.Exception
|
import Control.Exception
|
||||||
|
import Data.Maybe
|
||||||
import Language.Haskell.GhcMod.CabalApi
|
import Language.Haskell.GhcMod.CabalApi
|
||||||
|
import Language.Haskell.GhcMod.Cradle
|
||||||
|
import Language.Haskell.GhcMod.Types
|
||||||
import Test.Hspec
|
import Test.Hspec
|
||||||
|
|
||||||
|
import Dir
|
||||||
|
|
||||||
spec :: Spec
|
spec :: Spec
|
||||||
spec = do
|
spec = do
|
||||||
describe "parseCabalFile" $ do
|
describe "parseCabalFile" $ do
|
||||||
it "throws an exception if the cabal file is broken" $ do
|
it "throws an exception if the cabal file is broken" $ do
|
||||||
parseCabalFile "test/data/broken-cabal/broken.cabal" `shouldThrow` (\(_::IOException) -> True)
|
parseCabalFile "test/data/broken-cabal/broken.cabal" `shouldThrow` (\(_::IOException) -> True)
|
||||||
|
|
||||||
|
describe "getCompilerOptions" $ do
|
||||||
|
it "gets necessary CompilerOptions" $ do
|
||||||
|
withDirectory "test/data/subdir1/subdir2" $ \dir -> do
|
||||||
|
cradle <- findCradle Nothing "7.6.3"
|
||||||
|
pkgDesc <- parseCabalFile $ fromJust $ cradleCabalFile cradle
|
||||||
|
res <- getCompilerOptions [] cradle pkgDesc
|
||||||
|
let res' = res { includeDirs = map (toRelativeDir dir) (includeDirs res) }
|
||||||
|
res' `shouldBe` CompilerOptions {ghcOptions = ["-XHaskell98"], includeDirs = ["test/data","test/data/dist/build","test/data/subdir1/subdir2","test/data/test"], depPackages = ["Cabal","base","template-haskell"]}
|
||||||
|
|
||||||
describe "cabalDependPackages" $ do
|
describe "cabalDependPackages" $ do
|
||||||
it "extracts dependent packages" $ do
|
it "extracts dependent packages" $ do
|
||||||
pkgs <- cabalDependPackages . cabalAllBuildInfo <$> parseCabalFile "test/data/cabalapi.cabal"
|
pkgs <- cabalDependPackages . cabalAllBuildInfo <$> parseCabalFile "test/data/cabalapi.cabal"
|
||||||
@ -22,6 +36,9 @@ spec = do
|
|||||||
it "extracts all hs-source-dirs" $ do
|
it "extracts all hs-source-dirs" $ do
|
||||||
dirs <- cabalSourceDirs . cabalAllBuildInfo <$> parseCabalFile "test/data/check-test-subdir/check-test-subdir.cabal"
|
dirs <- cabalSourceDirs . cabalAllBuildInfo <$> parseCabalFile "test/data/check-test-subdir/check-test-subdir.cabal"
|
||||||
dirs `shouldBe` ["src", "test"]
|
dirs `shouldBe` ["src", "test"]
|
||||||
|
it "extracts all hs-source-dirs including \".\"" $ do
|
||||||
|
dirs <- cabalSourceDirs . cabalAllBuildInfo <$> parseCabalFile "test/data/cabalapi.cabal"
|
||||||
|
dirs `shouldBe` [".", "test"]
|
||||||
|
|
||||||
describe "cabalAllBuildInfo" $ do
|
describe "cabalAllBuildInfo" $ do
|
||||||
it "extracts build info" $ do
|
it "extracts build info" $ do
|
||||||
|
@ -1,7 +1,6 @@
|
|||||||
module CradleSpec where
|
module CradleSpec where
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Data.List (isPrefixOf)
|
|
||||||
import Language.Haskell.GhcMod
|
import Language.Haskell.GhcMod
|
||||||
import System.Directory (canonicalizePath)
|
import System.Directory (canonicalizePath)
|
||||||
import System.FilePath (addTrailingPathSeparator, (</>))
|
import System.FilePath (addTrailingPathSeparator, (</>))
|
||||||
@ -65,12 +64,3 @@ relativeCradle dir cradle = Cradle {
|
|||||||
, cradleCabalFile = toRelativeDir dir <$> cradleCabalFile cradle
|
, cradleCabalFile = toRelativeDir dir <$> cradleCabalFile cradle
|
||||||
, cradlePackageConf = toRelativeDir dir <$> cradlePackageConf cradle
|
, cradlePackageConf = toRelativeDir dir <$> cradlePackageConf cradle
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
toRelativeDir :: FilePath -> FilePath -> FilePath
|
|
||||||
toRelativeDir dir file
|
|
||||||
| dir' `isPrefixOf` file = drop len file
|
|
||||||
| otherwise = file
|
|
||||||
where
|
|
||||||
dir' = addTrailingPathSeparator dir
|
|
||||||
len = length dir'
|
|
||||||
|
12
test/Dir.hs
12
test/Dir.hs
@ -1,7 +1,9 @@
|
|||||||
module Dir where
|
module Dir where
|
||||||
|
|
||||||
import System.Directory
|
|
||||||
import Control.Exception as E
|
import Control.Exception as E
|
||||||
|
import Data.List (isPrefixOf)
|
||||||
|
import System.Directory
|
||||||
|
import System.FilePath (addTrailingPathSeparator)
|
||||||
|
|
||||||
withDirectory_ :: FilePath -> IO a -> IO a
|
withDirectory_ :: FilePath -> IO a -> IO a
|
||||||
withDirectory_ dir action = bracket getCurrentDirectory
|
withDirectory_ dir action = bracket getCurrentDirectory
|
||||||
@ -12,3 +14,11 @@ withDirectory :: FilePath -> (FilePath -> IO a) -> IO a
|
|||||||
withDirectory dir action = bracket getCurrentDirectory
|
withDirectory dir action = bracket getCurrentDirectory
|
||||||
setCurrentDirectory
|
setCurrentDirectory
|
||||||
(\d -> setCurrentDirectory dir >> action d)
|
(\d -> setCurrentDirectory dir >> action d)
|
||||||
|
|
||||||
|
toRelativeDir :: FilePath -> FilePath -> FilePath
|
||||||
|
toRelativeDir dir file
|
||||||
|
| dir' `isPrefixOf` file = drop len file
|
||||||
|
| otherwise = file
|
||||||
|
where
|
||||||
|
dir' = addTrailingPathSeparator dir
|
||||||
|
len = length dir'
|
||||||
|
Loading…
Reference in New Issue
Block a user