{-# LANGUAGE CPP #-} module Development.Shake.Cabal ( getCabalDeps , getCabalDepsV ) where import Control.Arrow import Control.Monad import Data.Foldable (toList) import Data.Maybe (catMaybes) #if __GLASGOW_HASKELL__ < 804 import Data.Semigroup #endif import Distribution.ModuleName import Distribution.PackageDescription import Distribution.PackageDescription.Parse import Distribution.Types.CondTree import Distribution.Verbosity libraryToFiles :: Library -> [FilePath] libraryToFiles lib = cs <> is <> ((<> ".hs") . toFilePath <$> explicitLibModules lib) where (cs, is) = (cSources &&& includes) $ libBuildInfo lib extract :: CondTree a b Library -> [Library] extract (CondNode d _ []) = [d] extract (CondNode d _ bs) = d : (g =<< bs) where g (CondBranch _ tb fb) = join $ catMaybes [Just $ extract tb, extract <$> fb] -- | Get library dependencies from a @.cabal@ file. This will only work for -- @.hs@ files; module signatures are not supported. getCabalDeps :: FilePath -> IO [FilePath] getCabalDeps = getCabalDepsV normal -- | Same as above, but we set the 'Verbosity' to be used during parsing. getCabalDepsV :: Verbosity -> FilePath -> IO [FilePath] getCabalDepsV v p = do pkg <- readGenericPackageDescription v p let extraSrc = extraSrcFiles $ packageDescription pkg libs = toList (condLibrary pkg) normalSrc = (libraryToFiles <=< extract) =<< libs pure (extraSrc <> normalSrc)