Fix findCabalFile
This commit is contained in:
parent
506cf18885
commit
9a8a3651d0
@ -32,7 +32,7 @@ cleanupCradle crdl = removeDirectoryRecursive $ cradleTempDir crdl
|
|||||||
|
|
||||||
cabalCradle :: FilePath -> IO Cradle
|
cabalCradle :: FilePath -> IO Cradle
|
||||||
cabalCradle wdir = do
|
cabalCradle wdir = do
|
||||||
Just cabalFile <- findCabalFiles wdir
|
Just cabalFile <- findCabalFile wdir
|
||||||
let cabalDir = takeDirectory cabalFile
|
let cabalDir = takeDirectory cabalFile
|
||||||
pkgDbStack <- getPackageDbStack cabalDir
|
pkgDbStack <- getPackageDbStack cabalDir
|
||||||
tmpDir <- newTempDir cabalDir
|
tmpDir <- newTempDir cabalDir
|
||||||
|
@ -28,16 +28,19 @@ type FileName = String
|
|||||||
-- is assumed to be the project directory. If only one cabal file exists in this
|
-- is assumed to be the project directory. If only one cabal file exists in this
|
||||||
-- directory it is returned otherwise @findCabalFiles@ throws 'GMENoCabalFile'
|
-- directory it is returned otherwise @findCabalFiles@ throws 'GMENoCabalFile'
|
||||||
-- or 'GMETooManyCabalFiles'
|
-- or 'GMETooManyCabalFiles'
|
||||||
findCabalFiles :: FilePath -> IO (Maybe FilePath)
|
findCabalFile :: FilePath -> IO (Maybe FilePath)
|
||||||
findCabalFiles directory = do
|
findCabalFile directory = do
|
||||||
-- Look for cabal files in @dir@ and all it's parent directories
|
-- Look for cabal files in @dir@ and all it's parent directories
|
||||||
dcs <- getCabalFiles `zipMapM` parents directory
|
dcs <- getCabalFiles `zipMapM` parents directory
|
||||||
-- Extract first non-empty list, which represents a directory with cabal
|
-- Extract first non-empty list, which represents a directory with cabal
|
||||||
-- files.
|
-- files.
|
||||||
case find (not . null) $ uncurry makeAbsolute `map` dcs of
|
case find (not . null) $ uncurry appendDir `map` dcs of
|
||||||
Just [] -> throw $ GMENoCabalFile
|
Just [] -> throw $ GMENoCabalFile
|
||||||
Just cfs@(_:_:_) -> throw $ GMETooManyCabalFiles cfs
|
Just cfs@(_:_:_) -> throw $ GMETooManyCabalFiles cfs
|
||||||
a -> return $ head <$> a
|
a -> return $ head <$> a
|
||||||
|
where
|
||||||
|
appendDir :: DirPath -> [FileName] -> [FilePath]
|
||||||
|
appendDir dir fs = (dir </>) `map` fs
|
||||||
|
|
||||||
-- | @getCabalFiles dir@. Find all files ending in @.cabal@ in @dir@.
|
-- | @getCabalFiles dir@. Find all files ending in @.cabal@ in @dir@.
|
||||||
getCabalFiles :: DirPath -> IO [FileName]
|
getCabalFiles :: DirPath -> IO [FileName]
|
||||||
@ -45,17 +48,13 @@ getCabalFiles dir =
|
|||||||
filterM isCabalFile =<< getDirectoryContents dir
|
filterM isCabalFile =<< getDirectoryContents dir
|
||||||
where
|
where
|
||||||
isCabalFile f = do
|
isCabalFile f = do
|
||||||
exists <- doesFileExist f
|
exists <- doesFileExist $ dir </> f
|
||||||
return (exists && takeExtension' f == ".cabal")
|
return (exists && takeExtension' f == ".cabal")
|
||||||
|
|
||||||
takeExtension' p = if takeFileName p == takeExtension p
|
takeExtension' p = if takeFileName p == takeExtension p
|
||||||
then ""
|
then ""
|
||||||
else takeExtension p
|
else takeExtension p
|
||||||
|
|
||||||
|
|
||||||
makeAbsolute :: DirPath -> [FileName] -> [FilePath]
|
|
||||||
makeAbsolute dir fs = (dir </>) `map` fs
|
|
||||||
|
|
||||||
zipMapM :: Monad m => (a -> m c) -> [a] -> m [(a,c)]
|
zipMapM :: Monad m => (a -> m c) -> [a] -> m [(a,c)]
|
||||||
zipMapM f as = mapM (\a -> liftM (a,) $ f a) as
|
zipMapM f as = mapM (\a -> liftM (a,) $ f a) as
|
||||||
|
|
||||||
|
@ -3,7 +3,6 @@
|
|||||||
module CabalApiSpec where
|
module CabalApiSpec where
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Data.Maybe
|
|
||||||
import Language.Haskell.GhcMod.CabalApi
|
import Language.Haskell.GhcMod.CabalApi
|
||||||
import Language.Haskell.GhcMod.Cradle
|
import Language.Haskell.GhcMod.Cradle
|
||||||
import Language.Haskell.GhcMod.Types
|
import Language.Haskell.GhcMod.Types
|
||||||
@ -35,7 +34,7 @@ spec = do
|
|||||||
cwd <- getCurrentDirectory
|
cwd <- getCurrentDirectory
|
||||||
withDirectory "test/data/subdir1/subdir2" $ \dir -> do
|
withDirectory "test/data/subdir1/subdir2" $ \dir -> do
|
||||||
crdl <- findCradle
|
crdl <- findCradle
|
||||||
let cabalFile = cradleCabalFile crdl
|
let Just cabalFile = cradleCabalFile crdl
|
||||||
pkgDesc <- runD $ parseCabalFile crdl cabalFile
|
pkgDesc <- runD $ parseCabalFile crdl cabalFile
|
||||||
res <- runD $ getCompilerOptions [] crdl pkgDesc
|
res <- runD $ getCompilerOptions [] crdl pkgDesc
|
||||||
let res' = res {
|
let res' = res {
|
||||||
|
@ -33,3 +33,10 @@ spec = do
|
|||||||
describe "getCabalFiles" $ do
|
describe "getCabalFiles" $ do
|
||||||
it "doesn't think $HOME/.cabal is a cabal file" $ do
|
it "doesn't think $HOME/.cabal is a cabal file" $ do
|
||||||
(getCabalFiles =<< getEnv "HOME") `shouldReturn` []
|
(getCabalFiles =<< getEnv "HOME") `shouldReturn` []
|
||||||
|
|
||||||
|
describe "findCabalFile" $ do
|
||||||
|
it "works" $ do
|
||||||
|
findCabalFile "test/data" `shouldReturn` Just "test/data/cabalapi.cabal"
|
||||||
|
|
||||||
|
it "finds cabal files in parent directories" $ do
|
||||||
|
findCabalFile "test/data/subdir1/subdir2" `shouldReturn` Just "test/data/cabalapi.cabal"
|
||||||
|
Loading…
Reference in New Issue
Block a user