{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RecordWildCards #-}
module Ormolu.Utils.Cabal
( CabalSearchResult (..),
CabalInfo (..),
Extension (..),
getCabalInfoForSourceFile,
findCabalFile,
parseCabalInfo,
)
where
import Control.Exception
import Control.Monad.IO.Class
import Data.ByteString qualified as B
import Data.Map.Lazy (Map)
import Data.Map.Lazy qualified as M
import Data.Maybe (maybeToList)
import Data.Set (Set)
import Data.Set qualified as Set
import Distribution.ModuleName (ModuleName)
import Distribution.ModuleName qualified as ModuleName
import Distribution.PackageDescription
import Distribution.PackageDescription.Parsec
import Distribution.Types.CondTree qualified as CT
import Distribution.Utils.Path (getSymbolicPath)
import Language.Haskell.Extension
import Ormolu.Config
import Ormolu.Exception
import Ormolu.Fixity
import Ormolu.Utils.IO (Cache, findClosestFileSatisfying, newCache, withCache)
import System.Directory
import System.FilePath
import System.IO.Unsafe (unsafePerformIO)
data CabalSearchResult
=
CabalNotFound
|
CabalDidNotMention CabalInfo
|
CabalFound CabalInfo
deriving (CabalSearchResult -> CabalSearchResult -> Bool
(CabalSearchResult -> CabalSearchResult -> Bool)
-> (CabalSearchResult -> CabalSearchResult -> Bool)
-> Eq CabalSearchResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CabalSearchResult -> CabalSearchResult -> Bool
== :: CabalSearchResult -> CabalSearchResult -> Bool
$c/= :: CabalSearchResult -> CabalSearchResult -> Bool
/= :: CabalSearchResult -> CabalSearchResult -> Bool
Eq, Int -> CabalSearchResult -> ShowS
[CabalSearchResult] -> ShowS
CabalSearchResult -> FilePath
(Int -> CabalSearchResult -> ShowS)
-> (CabalSearchResult -> FilePath)
-> ([CabalSearchResult] -> ShowS)
-> Show CabalSearchResult
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CabalSearchResult -> ShowS
showsPrec :: Int -> CabalSearchResult -> ShowS
$cshow :: CabalSearchResult -> FilePath
show :: CabalSearchResult -> FilePath
$cshowList :: [CabalSearchResult] -> ShowS
showList :: [CabalSearchResult] -> ShowS
Show)
data CabalInfo = CabalInfo
{
CabalInfo -> PackageName
ciPackageName :: !PackageName,
CabalInfo -> [DynOption]
ciDynOpts :: ![DynOption],
CabalInfo -> Set PackageName
ciDependencies :: !(Set PackageName),
CabalInfo -> FilePath
ciCabalFilePath :: !FilePath,
CabalInfo -> [ModuleName]
ciModules :: ![ModuleName]
}
deriving (CabalInfo -> CabalInfo -> Bool
(CabalInfo -> CabalInfo -> Bool)
-> (CabalInfo -> CabalInfo -> Bool) -> Eq CabalInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CabalInfo -> CabalInfo -> Bool
== :: CabalInfo -> CabalInfo -> Bool
$c/= :: CabalInfo -> CabalInfo -> Bool
/= :: CabalInfo -> CabalInfo -> Bool
Eq, Int -> CabalInfo -> ShowS
[CabalInfo] -> ShowS
CabalInfo -> FilePath
(Int -> CabalInfo -> ShowS)
-> (CabalInfo -> FilePath)
-> ([CabalInfo] -> ShowS)
-> Show CabalInfo
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CabalInfo -> ShowS
showsPrec :: Int -> CabalInfo -> ShowS
$cshow :: CabalInfo -> FilePath
show :: CabalInfo -> FilePath
$cshowList :: [CabalInfo] -> ShowS
showList :: [CabalInfo] -> ShowS
Show)
getCabalInfoForSourceFile ::
(MonadIO m) =>
FilePath ->
m CabalSearchResult
getCabalInfoForSourceFile :: forall (m :: * -> *). MonadIO m => FilePath -> m CabalSearchResult
getCabalInfoForSourceFile FilePath
sourceFile =
IO (Maybe FilePath) -> m (Maybe FilePath)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (FilePath -> IO (Maybe FilePath)
forall (m :: * -> *). MonadIO m => FilePath -> m (Maybe FilePath)
findCabalFile FilePath
sourceFile) m (Maybe FilePath)
-> (Maybe FilePath -> m CabalSearchResult) -> m CabalSearchResult
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Just FilePath
cabalFile -> do
(Bool
mentioned, CabalInfo
cabalInfo) <- FilePath -> FilePath -> m (Bool, CabalInfo)
forall (m :: * -> *).
MonadIO m =>
FilePath -> FilePath -> m (Bool, CabalInfo)
parseCabalInfo FilePath
cabalFile FilePath
sourceFile
CabalSearchResult -> m CabalSearchResult
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return
( if Bool
mentioned
then CabalInfo -> CabalSearchResult
CabalFound CabalInfo
cabalInfo
else CabalInfo -> CabalSearchResult
CabalDidNotMention CabalInfo
cabalInfo
)
Maybe FilePath
Nothing -> CabalSearchResult -> m CabalSearchResult
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return CabalSearchResult
CabalNotFound
findCabalFile ::
(MonadIO m) =>
FilePath ->
m (Maybe FilePath)
findCabalFile :: forall (m :: * -> *). MonadIO m => FilePath -> m (Maybe FilePath)
findCabalFile = (FilePath -> Bool) -> FilePath -> m (Maybe FilePath)
forall (m :: * -> *).
MonadIO m =>
(FilePath -> Bool) -> FilePath -> m (Maybe FilePath)
findClosestFileSatisfying ((FilePath -> Bool) -> FilePath -> m (Maybe FilePath))
-> (FilePath -> Bool) -> FilePath -> m (Maybe FilePath)
forall a b. (a -> b) -> a -> b
$ \FilePath
x ->
ShowS
takeExtension FilePath
x FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
".cabal"
data CachedCabalFile = CachedCabalFile
{
CachedCabalFile -> GenericPackageDescription
genericPackageDescription :: GenericPackageDescription,
CachedCabalFile -> Map FilePath ([DynOption], [PackageName])
extensionsAndDeps :: Map FilePath ([DynOption], [PackageName]),
CachedCabalFile -> [ModuleName]
localModules :: [ModuleName]
}
deriving (Int -> CachedCabalFile -> ShowS
[CachedCabalFile] -> ShowS
CachedCabalFile -> FilePath
(Int -> CachedCabalFile -> ShowS)
-> (CachedCabalFile -> FilePath)
-> ([CachedCabalFile] -> ShowS)
-> Show CachedCabalFile
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CachedCabalFile -> ShowS
showsPrec :: Int -> CachedCabalFile -> ShowS
$cshow :: CachedCabalFile -> FilePath
show :: CachedCabalFile -> FilePath
$cshowList :: [CachedCabalFile] -> ShowS
showList :: [CachedCabalFile] -> ShowS
Show)
cacheRef :: Cache FilePath CachedCabalFile
cacheRef :: Cache FilePath CachedCabalFile
cacheRef = IO (Cache FilePath CachedCabalFile)
-> Cache FilePath CachedCabalFile
forall a. IO a -> a
unsafePerformIO IO (Cache FilePath CachedCabalFile)
forall k v. Ord k => IO (Cache k v)
newCache
{-# NOINLINE cacheRef #-}
parseCabalInfo ::
(MonadIO m) =>
FilePath ->
FilePath ->
m (Bool, CabalInfo)
parseCabalInfo :: forall (m :: * -> *).
MonadIO m =>
FilePath -> FilePath -> m (Bool, CabalInfo)
parseCabalInfo FilePath
cabalFileAsGiven FilePath
sourceFileAsGiven = IO (Bool, CabalInfo) -> m (Bool, CabalInfo)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, CabalInfo) -> m (Bool, CabalInfo))
-> IO (Bool, CabalInfo) -> m (Bool, CabalInfo)
forall a b. (a -> b) -> a -> b
$ do
FilePath
cabalFile <- FilePath -> IO FilePath
makeAbsolute FilePath
cabalFileAsGiven
FilePath
sourceFileAbs <- FilePath -> IO FilePath
makeAbsolute FilePath
sourceFileAsGiven
CachedCabalFile {[ModuleName]
Map FilePath ([DynOption], [PackageName])
GenericPackageDescription
genericPackageDescription :: CachedCabalFile -> GenericPackageDescription
extensionsAndDeps :: CachedCabalFile -> Map FilePath ([DynOption], [PackageName])
localModules :: CachedCabalFile -> [ModuleName]
genericPackageDescription :: GenericPackageDescription
extensionsAndDeps :: Map FilePath ([DynOption], [PackageName])
localModules :: [ModuleName]
..} <- Cache FilePath CachedCabalFile
-> FilePath -> IO CachedCabalFile -> IO CachedCabalFile
forall k v. Ord k => Cache k v -> k -> IO v -> IO v
withCache Cache FilePath CachedCabalFile
cacheRef FilePath
cabalFile (IO CachedCabalFile -> IO CachedCabalFile)
-> IO CachedCabalFile -> IO CachedCabalFile
forall a b. (a -> b) -> a -> b
$ do
ByteString
cabalFileBs <- FilePath -> IO ByteString
B.readFile FilePath
cabalFile
GenericPackageDescription
genericPackageDescription <-
Either (Maybe Version, NonEmpty PError) GenericPackageDescription
-> ((Maybe Version, NonEmpty PError)
-> IO GenericPackageDescription)
-> IO GenericPackageDescription
forall (f :: * -> *) e a.
Applicative f =>
Either e a -> (e -> f a) -> f a
whenLeft (([PWarning],
Either (Maybe Version, NonEmpty PError) GenericPackageDescription)
-> Either
(Maybe Version, NonEmpty PError) GenericPackageDescription
forall a b. (a, b) -> b
snd (([PWarning],
Either (Maybe Version, NonEmpty PError) GenericPackageDescription)
-> Either
(Maybe Version, NonEmpty PError) GenericPackageDescription)
-> (ParseResult GenericPackageDescription
-> ([PWarning],
Either (Maybe Version, NonEmpty PError) GenericPackageDescription))
-> ParseResult GenericPackageDescription
-> Either
(Maybe Version, NonEmpty PError) GenericPackageDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParseResult GenericPackageDescription
-> ([PWarning],
Either (Maybe Version, NonEmpty PError) GenericPackageDescription)
forall a.
ParseResult a
-> ([PWarning], Either (Maybe Version, NonEmpty PError) a)
runParseResult (ParseResult GenericPackageDescription
-> Either
(Maybe Version, NonEmpty PError) GenericPackageDescription)
-> ParseResult GenericPackageDescription
-> Either
(Maybe Version, NonEmpty PError) GenericPackageDescription
forall a b. (a -> b) -> a -> b
$ ByteString -> ParseResult GenericPackageDescription
parseGenericPackageDescription ByteString
cabalFileBs) (((Maybe Version, NonEmpty PError) -> IO GenericPackageDescription)
-> IO GenericPackageDescription)
-> ((Maybe Version, NonEmpty PError)
-> IO GenericPackageDescription)
-> IO GenericPackageDescription
forall a b. (a -> b) -> a -> b
$
OrmoluException -> IO GenericPackageDescription
forall e a. Exception e => e -> IO a
throwIO (OrmoluException -> IO GenericPackageDescription)
-> ((Maybe Version, NonEmpty PError) -> OrmoluException)
-> (Maybe Version, NonEmpty PError)
-> IO GenericPackageDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> NonEmpty PError -> OrmoluException
OrmoluCabalFileParsingFailed FilePath
cabalFile (NonEmpty PError -> OrmoluException)
-> ((Maybe Version, NonEmpty PError) -> NonEmpty PError)
-> (Maybe Version, NonEmpty PError)
-> OrmoluException
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe Version, NonEmpty PError) -> NonEmpty PError
forall a b. (a, b) -> b
snd
let extensionsAndDeps :: Map FilePath ([DynOption], [PackageName])
extensionsAndDeps =
FilePath
-> GenericPackageDescription
-> Map FilePath ([DynOption], [PackageName])
getExtensionAndDepsMap FilePath
cabalFile GenericPackageDescription
genericPackageDescription
localModules :: [ModuleName]
localModules = GenericPackageDescription -> [ModuleName]
getLocalModules GenericPackageDescription
genericPackageDescription
CachedCabalFile -> IO CachedCabalFile
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure CachedCabalFile {[ModuleName]
Map FilePath ([DynOption], [PackageName])
GenericPackageDescription
genericPackageDescription :: GenericPackageDescription
extensionsAndDeps :: Map FilePath ([DynOption], [PackageName])
localModules :: [ModuleName]
genericPackageDescription :: GenericPackageDescription
extensionsAndDeps :: Map FilePath ([DynOption], [PackageName])
localModules :: [ModuleName]
..}
let ([DynOption]
dynOpts, [PackageName]
dependencies, Bool
mentioned) =
case FilePath
-> Map FilePath ([DynOption], [PackageName])
-> Maybe ([DynOption], [PackageName])
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (ShowS
dropExtensions FilePath
sourceFileAbs) Map FilePath ([DynOption], [PackageName])
extensionsAndDeps of
Maybe ([DynOption], [PackageName])
Nothing -> ([], Set PackageName -> [PackageName]
forall a. Set a -> [a]
Set.toList Set PackageName
defaultDependencies, Bool
False)
Just ([DynOption]
dynOpts', [PackageName]
dependencies') -> ([DynOption]
dynOpts', [PackageName]
dependencies', Bool
True)
pdesc :: PackageDescription
pdesc = GenericPackageDescription -> PackageDescription
packageDescription GenericPackageDescription
genericPackageDescription
(Bool, CabalInfo) -> IO (Bool, CabalInfo)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
( Bool
mentioned,
CabalInfo
{ ciPackageName :: PackageName
ciPackageName = PackageIdentifier -> PackageName
pkgName (PackageDescription -> PackageIdentifier
package PackageDescription
pdesc),
ciDynOpts :: [DynOption]
ciDynOpts = [DynOption]
dynOpts,
ciDependencies :: Set PackageName
ciDependencies = [PackageName] -> Set PackageName
forall a. Ord a => [a] -> Set a
Set.fromList [PackageName]
dependencies,
ciCabalFilePath :: FilePath
ciCabalFilePath = FilePath
cabalFile,
ciModules :: [ModuleName]
ciModules = [ModuleName]
localModules
}
)
where
whenLeft :: (Applicative f) => Either e a -> (e -> f a) -> f a
whenLeft :: forall (f :: * -> *) e a.
Applicative f =>
Either e a -> (e -> f a) -> f a
whenLeft Either e a
eitha e -> f a
ma = (e -> f a) -> (a -> f a) -> Either e a -> f a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either e -> f a
ma a -> f a
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Either e a
eitha
getLocalModules :: GenericPackageDescription -> [ModuleName]
getLocalModules :: GenericPackageDescription -> [ModuleName]
getLocalModules = GenericPackageDescription -> [ModuleName]
extractPackageModules
where
extractPackageModules :: GenericPackageDescription -> [ModuleName]
extractPackageModules :: GenericPackageDescription -> [ModuleName]
extractPackageModules GenericPackageDescription {[(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
[(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
[(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
[(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
[(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
[PackageFlag]
Maybe (CondTree ConfVar [Dependency] Library)
Maybe Version
PackageDescription
packageDescription :: GenericPackageDescription -> PackageDescription
packageDescription :: PackageDescription
gpdScannedVersion :: Maybe Version
genPackageFlags :: [PackageFlag]
condLibrary :: Maybe (CondTree ConfVar [Dependency] Library)
condSubLibraries :: [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
condForeignLibs :: [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
condExecutables :: [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
condTestSuites :: [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
condBenchmarks :: [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
condBenchmarks :: GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
condTestSuites :: GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
condExecutables :: GenericPackageDescription
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
condForeignLibs :: GenericPackageDescription
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] ForeignLib)]
condSubLibraries :: GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
condLibrary :: GenericPackageDescription
-> Maybe (CondTree ConfVar [Dependency] Library)
genPackageFlags :: GenericPackageDescription -> [PackageFlag]
gpdScannedVersion :: GenericPackageDescription -> Maybe Version
..} =
[[ModuleName]] -> [ModuleName]
forall a. Monoid a => [a] -> a
mconcat
[ [ModuleName]
-> (CondTree ConfVar [Dependency] Library -> [ModuleName])
-> Maybe (CondTree ConfVar [Dependency] Library)
-> [ModuleName]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (Library -> [ModuleName]
extractLibraryModules (Library -> [ModuleName])
-> (CondTree ConfVar [Dependency] Library -> Library)
-> CondTree ConfVar [Dependency] Library
-> [ModuleName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CondTree ConfVar [Dependency] Library -> Library
forall v c a. CondTree v c a -> a
condTreeData) Maybe (CondTree ConfVar [Dependency] Library)
condLibrary,
Library -> [ModuleName]
extractLibraryModules (Library -> [ModuleName])
-> ((UnqualComponentName, CondTree ConfVar [Dependency] Library)
-> Library)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Library)
-> [ModuleName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CondTree ConfVar [Dependency] Library -> Library
forall v c a. CondTree v c a -> a
condTreeData (CondTree ConfVar [Dependency] Library -> Library)
-> ((UnqualComponentName, CondTree ConfVar [Dependency] Library)
-> CondTree ConfVar [Dependency] Library)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Library)
-> Library
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UnqualComponentName, CondTree ConfVar [Dependency] Library)
-> CondTree ConfVar [Dependency] Library
forall a b. (a, b) -> b
snd ((UnqualComponentName, CondTree ConfVar [Dependency] Library)
-> [ModuleName])
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> [ModuleName]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
condSubLibraries,
ForeignLib -> [ModuleName]
extractForeignLibraryModules (ForeignLib -> [ModuleName])
-> ((UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)
-> ForeignLib)
-> (UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)
-> [ModuleName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CondTree ConfVar [Dependency] ForeignLib -> ForeignLib
forall v c a. CondTree v c a -> a
condTreeData (CondTree ConfVar [Dependency] ForeignLib -> ForeignLib)
-> ((UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)
-> CondTree ConfVar [Dependency] ForeignLib)
-> (UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)
-> ForeignLib
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)
-> CondTree ConfVar [Dependency] ForeignLib
forall a b. (a, b) -> b
snd ((UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)
-> [ModuleName])
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] ForeignLib)]
-> [ModuleName]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
condForeignLibs,
Executable -> [ModuleName]
extractExecutableModules (Executable -> [ModuleName])
-> ((UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> Executable)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> [ModuleName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CondTree ConfVar [Dependency] Executable -> Executable
forall v c a. CondTree v c a -> a
condTreeData (CondTree ConfVar [Dependency] Executable -> Executable)
-> ((UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> CondTree ConfVar [Dependency] Executable)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> Executable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> CondTree ConfVar [Dependency] Executable
forall a b. (a, b) -> b
snd ((UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> [ModuleName])
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> [ModuleName]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
condExecutables,
TestSuite -> [ModuleName]
extractTestSuiteModules (TestSuite -> [ModuleName])
-> ((UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> TestSuite)
-> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> [ModuleName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CondTree ConfVar [Dependency] TestSuite -> TestSuite
forall v c a. CondTree v c a -> a
condTreeData (CondTree ConfVar [Dependency] TestSuite -> TestSuite)
-> ((UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> CondTree ConfVar [Dependency] TestSuite)
-> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> TestSuite
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> CondTree ConfVar [Dependency] TestSuite
forall a b. (a, b) -> b
snd ((UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> [ModuleName])
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [ModuleName]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
condTestSuites,
Benchmark -> [ModuleName]
extractBenchmarkModules (Benchmark -> [ModuleName])
-> ((UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> Benchmark)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> [ModuleName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CondTree ConfVar [Dependency] Benchmark -> Benchmark
forall v c a. CondTree v c a -> a
condTreeData (CondTree ConfVar [Dependency] Benchmark -> Benchmark)
-> ((UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> CondTree ConfVar [Dependency] Benchmark)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> Benchmark
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> CondTree ConfVar [Dependency] Benchmark
forall a b. (a, b) -> b
snd ((UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> [ModuleName])
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> [ModuleName]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
condBenchmarks
]
extractLibraryModules :: Library -> [ModuleName]
extractLibraryModules :: Library -> [ModuleName]
extractLibraryModules Library {Bool
[ModuleName]
[ModuleReexport]
LibraryVisibility
LibraryName
BuildInfo
libName :: LibraryName
exposedModules :: [ModuleName]
reexportedModules :: [ModuleReexport]
signatures :: [ModuleName]
libExposed :: Bool
libVisibility :: LibraryVisibility
libBuildInfo :: BuildInfo
libBuildInfo :: Library -> BuildInfo
libVisibility :: Library -> LibraryVisibility
libExposed :: Library -> Bool
signatures :: Library -> [ModuleName]
reexportedModules :: Library -> [ModuleReexport]
exposedModules :: Library -> [ModuleName]
libName :: Library -> LibraryName
..} = [[ModuleName]] -> [ModuleName]
forall a. Monoid a => [a] -> a
mconcat [[ModuleName]
exposedModules, BuildInfo -> [ModuleName]
extractBuildInfoModules BuildInfo
libBuildInfo]
extractForeignLibraryModules :: ForeignLib -> [ModuleName]
extractForeignLibraryModules :: ForeignLib -> [ModuleName]
extractForeignLibraryModules = BuildInfo -> [ModuleName]
extractBuildInfoModules (BuildInfo -> [ModuleName])
-> (ForeignLib -> BuildInfo) -> ForeignLib -> [ModuleName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignLib -> BuildInfo
foreignLibBuildInfo
extractExecutableModules :: Executable -> [ModuleName]
extractExecutableModules :: Executable -> [ModuleName]
extractExecutableModules = BuildInfo -> [ModuleName]
extractBuildInfoModules (BuildInfo -> [ModuleName])
-> (Executable -> BuildInfo) -> Executable -> [ModuleName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Executable -> BuildInfo
buildInfo
extractTestSuiteModules :: TestSuite -> [ModuleName]
extractTestSuiteModules :: TestSuite -> [ModuleName]
extractTestSuiteModules = BuildInfo -> [ModuleName]
extractBuildInfoModules (BuildInfo -> [ModuleName])
-> (TestSuite -> BuildInfo) -> TestSuite -> [ModuleName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestSuite -> BuildInfo
testBuildInfo
extractBenchmarkModules :: Benchmark -> [ModuleName]
extractBenchmarkModules :: Benchmark -> [ModuleName]
extractBenchmarkModules = BuildInfo -> [ModuleName]
extractBuildInfoModules (BuildInfo -> [ModuleName])
-> (Benchmark -> BuildInfo) -> Benchmark -> [ModuleName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Benchmark -> BuildInfo
benchmarkBuildInfo
extractBuildInfoModules :: BuildInfo -> [ModuleName]
extractBuildInfoModules :: BuildInfo -> [ModuleName]
extractBuildInfoModules BuildInfo {Bool
[FilePath]
[(FilePath, FilePath)]
[PkgconfigDependency]
[ModuleName]
[SymbolicPath Include 'File]
[SymbolicPath Pkg 'File]
[SymbolicPath Pkg ('Dir Framework)]
[SymbolicPath Pkg ('Dir Lib)]
[SymbolicPath Pkg ('Dir Include)]
[SymbolicPath Pkg ('Dir Source)]
[RelativePath Framework 'File]
[RelativePath Include 'File]
[Mixin]
[LegacyExeDependency]
[ExeDependency]
[Dependency]
[Extension]
[Language]
Maybe Language
PerCompilerFlavor [FilePath]
buildable :: Bool
buildTools :: [LegacyExeDependency]
buildToolDepends :: [ExeDependency]
cppOptions :: [FilePath]
asmOptions :: [FilePath]
cmmOptions :: [FilePath]
ccOptions :: [FilePath]
cxxOptions :: [FilePath]
ldOptions :: [FilePath]
hsc2hsOptions :: [FilePath]
pkgconfigDepends :: [PkgconfigDependency]
frameworks :: [RelativePath Framework 'File]
extraFrameworkDirs :: [SymbolicPath Pkg ('Dir Framework)]
asmSources :: [SymbolicPath Pkg 'File]
cmmSources :: [SymbolicPath Pkg 'File]
cSources :: [SymbolicPath Pkg 'File]
cxxSources :: [SymbolicPath Pkg 'File]
jsSources :: [SymbolicPath Pkg 'File]
hsSourceDirs :: [SymbolicPath Pkg ('Dir Source)]
otherModules :: [ModuleName]
virtualModules :: [ModuleName]
autogenModules :: [ModuleName]
defaultLanguage :: Maybe Language
otherLanguages :: [Language]
defaultExtensions :: [Extension]
otherExtensions :: [Extension]
oldExtensions :: [Extension]
extraLibs :: [FilePath]
extraLibsStatic :: [FilePath]
extraGHCiLibs :: [FilePath]
extraBundledLibs :: [FilePath]
extraLibFlavours :: [FilePath]
extraDynLibFlavours :: [FilePath]
extraLibDirs :: [SymbolicPath Pkg ('Dir Lib)]
extraLibDirsStatic :: [SymbolicPath Pkg ('Dir Lib)]
includeDirs :: [SymbolicPath Pkg ('Dir Include)]
includes :: [SymbolicPath Include 'File]
autogenIncludes :: [RelativePath Include 'File]
installIncludes :: [RelativePath Include 'File]
options :: PerCompilerFlavor [FilePath]
profOptions :: PerCompilerFlavor [FilePath]
sharedOptions :: PerCompilerFlavor [FilePath]
profSharedOptions :: PerCompilerFlavor [FilePath]
staticOptions :: PerCompilerFlavor [FilePath]
customFieldsBI :: [(FilePath, FilePath)]
targetBuildDepends :: [Dependency]
mixins :: [Mixin]
mixins :: BuildInfo -> [Mixin]
targetBuildDepends :: BuildInfo -> [Dependency]
customFieldsBI :: BuildInfo -> [(FilePath, FilePath)]
staticOptions :: BuildInfo -> PerCompilerFlavor [FilePath]
profSharedOptions :: BuildInfo -> PerCompilerFlavor [FilePath]
sharedOptions :: BuildInfo -> PerCompilerFlavor [FilePath]
profOptions :: BuildInfo -> PerCompilerFlavor [FilePath]
options :: BuildInfo -> PerCompilerFlavor [FilePath]
installIncludes :: BuildInfo -> [RelativePath Include 'File]
autogenIncludes :: BuildInfo -> [RelativePath Include 'File]
includes :: BuildInfo -> [SymbolicPath Include 'File]
includeDirs :: BuildInfo -> [SymbolicPath Pkg ('Dir Include)]
extraLibDirsStatic :: BuildInfo -> [SymbolicPath Pkg ('Dir Lib)]
extraLibDirs :: BuildInfo -> [SymbolicPath Pkg ('Dir Lib)]
extraDynLibFlavours :: BuildInfo -> [FilePath]
extraLibFlavours :: BuildInfo -> [FilePath]
extraBundledLibs :: BuildInfo -> [FilePath]
extraGHCiLibs :: BuildInfo -> [FilePath]
extraLibsStatic :: BuildInfo -> [FilePath]
extraLibs :: BuildInfo -> [FilePath]
oldExtensions :: BuildInfo -> [Extension]
otherExtensions :: BuildInfo -> [Extension]
defaultExtensions :: BuildInfo -> [Extension]
otherLanguages :: BuildInfo -> [Language]
defaultLanguage :: BuildInfo -> Maybe Language
autogenModules :: BuildInfo -> [ModuleName]
virtualModules :: BuildInfo -> [ModuleName]
otherModules :: BuildInfo -> [ModuleName]
hsSourceDirs :: BuildInfo -> [SymbolicPath Pkg ('Dir Source)]
jsSources :: BuildInfo -> [SymbolicPath Pkg 'File]
cxxSources :: BuildInfo -> [SymbolicPath Pkg 'File]
cSources :: BuildInfo -> [SymbolicPath Pkg 'File]
cmmSources :: BuildInfo -> [SymbolicPath Pkg 'File]
asmSources :: BuildInfo -> [SymbolicPath Pkg 'File]
extraFrameworkDirs :: BuildInfo -> [SymbolicPath Pkg ('Dir Framework)]
frameworks :: BuildInfo -> [RelativePath Framework 'File]
pkgconfigDepends :: BuildInfo -> [PkgconfigDependency]
hsc2hsOptions :: BuildInfo -> [FilePath]
ldOptions :: BuildInfo -> [FilePath]
cxxOptions :: BuildInfo -> [FilePath]
ccOptions :: BuildInfo -> [FilePath]
cmmOptions :: BuildInfo -> [FilePath]
asmOptions :: BuildInfo -> [FilePath]
cppOptions :: BuildInfo -> [FilePath]
buildToolDepends :: BuildInfo -> [ExeDependency]
buildTools :: BuildInfo -> [LegacyExeDependency]
buildable :: BuildInfo -> Bool
..} = [[ModuleName]] -> [ModuleName]
forall a. Monoid a => [a] -> a
mconcat [[ModuleName]
otherModules, [ModuleName]
virtualModules, [ModuleName]
autogenModules]
getExtensionAndDepsMap ::
FilePath ->
GenericPackageDescription ->
Map FilePath ([DynOption], [PackageName])
getExtensionAndDepsMap :: FilePath
-> GenericPackageDescription
-> Map FilePath ([DynOption], [PackageName])
getExtensionAndDepsMap FilePath
cabalFile GenericPackageDescription {[(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
[(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
[(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
[(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
[(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
[PackageFlag]
Maybe (CondTree ConfVar [Dependency] Library)
Maybe Version
PackageDescription
packageDescription :: GenericPackageDescription -> PackageDescription
condBenchmarks :: GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
condTestSuites :: GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
condExecutables :: GenericPackageDescription
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
condForeignLibs :: GenericPackageDescription
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] ForeignLib)]
condSubLibraries :: GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
condLibrary :: GenericPackageDescription
-> Maybe (CondTree ConfVar [Dependency] Library)
genPackageFlags :: GenericPackageDescription -> [PackageFlag]
gpdScannedVersion :: GenericPackageDescription -> Maybe Version
packageDescription :: PackageDescription
gpdScannedVersion :: Maybe Version
genPackageFlags :: [PackageFlag]
condLibrary :: Maybe (CondTree ConfVar [Dependency] Library)
condSubLibraries :: [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
condForeignLibs :: [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
condExecutables :: [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
condTestSuites :: [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
condBenchmarks :: [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
..} =
[Map FilePath ([DynOption], [PackageName])]
-> Map FilePath ([DynOption], [PackageName])
forall (f :: * -> *) k a.
(Foldable f, Ord k) =>
f (Map k a) -> Map k a
M.unions ([Map FilePath ([DynOption], [PackageName])]
-> Map FilePath ([DynOption], [PackageName]))
-> ([[Map FilePath ([DynOption], [PackageName])]]
-> [Map FilePath ([DynOption], [PackageName])])
-> [[Map FilePath ([DynOption], [PackageName])]]
-> Map FilePath ([DynOption], [PackageName])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Map FilePath ([DynOption], [PackageName])]]
-> [Map FilePath ([DynOption], [PackageName])]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Map FilePath ([DynOption], [PackageName])]]
-> Map FilePath ([DynOption], [PackageName]))
-> [[Map FilePath ([DynOption], [PackageName])]]
-> Map FilePath ([DynOption], [PackageName])
forall a b. (a -> b) -> a -> b
$
[ (Library -> ([FilePath], ([DynOption], [PackageName])))
-> CondTree ConfVar [Dependency] Library
-> Map FilePath ([DynOption], [PackageName])
forall {k} {a} {c} {a} {v}.
(Ord k, Semigroup a, Semigroup c) =>
(a -> ([k], a)) -> CondTree v c a -> Map k a
buildMap Library -> ([FilePath], ([DynOption], [PackageName]))
extractFromLibrary (CondTree ConfVar [Dependency] Library
-> Map FilePath ([DynOption], [PackageName]))
-> [CondTree ConfVar [Dependency] Library]
-> [Map FilePath ([DynOption], [PackageName])]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [CondTree ConfVar [Dependency] Library]
lib [CondTree ConfVar [Dependency] Library]
-> [CondTree ConfVar [Dependency] Library]
-> [CondTree ConfVar [Dependency] Library]
forall a. [a] -> [a] -> [a]
++ [CondTree ConfVar [Dependency] Library]
sublibs,
(Executable -> ([FilePath], ([DynOption], [PackageName])))
-> CondTree ConfVar [Dependency] Executable
-> Map FilePath ([DynOption], [PackageName])
forall {k} {a} {c} {a} {v}.
(Ord k, Semigroup a, Semigroup c) =>
(a -> ([k], a)) -> CondTree v c a -> Map k a
buildMap Executable -> ([FilePath], ([DynOption], [PackageName]))
extractFromExecutable (CondTree ConfVar [Dependency] Executable
-> Map FilePath ([DynOption], [PackageName]))
-> ((UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> CondTree ConfVar [Dependency] Executable)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> Map FilePath ([DynOption], [PackageName])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> CondTree ConfVar [Dependency] Executable
forall a b. (a, b) -> b
snd ((UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> Map FilePath ([DynOption], [PackageName]))
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> [Map FilePath ([DynOption], [PackageName])]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
condExecutables,
(TestSuite -> ([FilePath], ([DynOption], [PackageName])))
-> CondTree ConfVar [Dependency] TestSuite
-> Map FilePath ([DynOption], [PackageName])
forall {k} {a} {c} {a} {v}.
(Ord k, Semigroup a, Semigroup c) =>
(a -> ([k], a)) -> CondTree v c a -> Map k a
buildMap TestSuite -> ([FilePath], ([DynOption], [PackageName]))
extractFromTestSuite (CondTree ConfVar [Dependency] TestSuite
-> Map FilePath ([DynOption], [PackageName]))
-> ((UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> CondTree ConfVar [Dependency] TestSuite)
-> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> Map FilePath ([DynOption], [PackageName])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> CondTree ConfVar [Dependency] TestSuite
forall a b. (a, b) -> b
snd ((UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> Map FilePath ([DynOption], [PackageName]))
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [Map FilePath ([DynOption], [PackageName])]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
condTestSuites,
(Benchmark -> ([FilePath], ([DynOption], [PackageName])))
-> CondTree ConfVar [Dependency] Benchmark
-> Map FilePath ([DynOption], [PackageName])
forall {k} {a} {c} {a} {v}.
(Ord k, Semigroup a, Semigroup c) =>
(a -> ([k], a)) -> CondTree v c a -> Map k a
buildMap Benchmark -> ([FilePath], ([DynOption], [PackageName]))
extractFromBenchmark (CondTree ConfVar [Dependency] Benchmark
-> Map FilePath ([DynOption], [PackageName]))
-> ((UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> CondTree ConfVar [Dependency] Benchmark)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> Map FilePath ([DynOption], [PackageName])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> CondTree ConfVar [Dependency] Benchmark
forall a b. (a, b) -> b
snd ((UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> Map FilePath ([DynOption], [PackageName]))
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> [Map FilePath ([DynOption], [PackageName])]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
condBenchmarks
]
where
lib :: [CondTree ConfVar [Dependency] Library]
lib = Maybe (CondTree ConfVar [Dependency] Library)
-> [CondTree ConfVar [Dependency] Library]
forall a. Maybe a -> [a]
maybeToList Maybe (CondTree ConfVar [Dependency] Library)
condLibrary
sublibs :: [CondTree ConfVar [Dependency] Library]
sublibs = (UnqualComponentName, CondTree ConfVar [Dependency] Library)
-> CondTree ConfVar [Dependency] Library
forall a b. (a, b) -> b
snd ((UnqualComponentName, CondTree ConfVar [Dependency] Library)
-> CondTree ConfVar [Dependency] Library)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> [CondTree ConfVar [Dependency] Library]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
condSubLibraries
buildMap :: (a -> ([k], a)) -> CondTree v c a -> Map k a
buildMap a -> ([k], a)
f CondTree v c a
a = [(k, a)] -> Map k a
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ((,a
extsAndDeps) (k -> (k, a)) -> [k] -> [(k, a)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [k]
files)
where
(a
mergedA, c
_) = CondTree v c a -> (a, c)
forall a c v.
(Semigroup a, Semigroup c) =>
CondTree v c a -> (a, c)
CT.ignoreConditions CondTree v c a
a
([k]
files, a
extsAndDeps) = a -> ([k], a)
f a
mergedA
extractFromBuildInfo :: [FilePath]
-> BuildInfo -> ([FilePath], ([DynOption], [PackageName]))
extractFromBuildInfo [FilePath]
extraModules BuildInfo {Bool
[FilePath]
[(FilePath, FilePath)]
[PkgconfigDependency]
[ModuleName]
[SymbolicPath Include 'File]
[SymbolicPath Pkg 'File]
[SymbolicPath Pkg ('Dir Framework)]
[SymbolicPath Pkg ('Dir Lib)]
[SymbolicPath Pkg ('Dir Include)]
[SymbolicPath Pkg ('Dir Source)]
[RelativePath Framework 'File]
[RelativePath Include 'File]
[Mixin]
[LegacyExeDependency]
[ExeDependency]
[Dependency]
[Extension]
[Language]
Maybe Language
PerCompilerFlavor [FilePath]
mixins :: BuildInfo -> [Mixin]
targetBuildDepends :: BuildInfo -> [Dependency]
customFieldsBI :: BuildInfo -> [(FilePath, FilePath)]
staticOptions :: BuildInfo -> PerCompilerFlavor [FilePath]
profSharedOptions :: BuildInfo -> PerCompilerFlavor [FilePath]
sharedOptions :: BuildInfo -> PerCompilerFlavor [FilePath]
profOptions :: BuildInfo -> PerCompilerFlavor [FilePath]
options :: BuildInfo -> PerCompilerFlavor [FilePath]
installIncludes :: BuildInfo -> [RelativePath Include 'File]
autogenIncludes :: BuildInfo -> [RelativePath Include 'File]
includes :: BuildInfo -> [SymbolicPath Include 'File]
includeDirs :: BuildInfo -> [SymbolicPath Pkg ('Dir Include)]
extraLibDirsStatic :: BuildInfo -> [SymbolicPath Pkg ('Dir Lib)]
extraLibDirs :: BuildInfo -> [SymbolicPath Pkg ('Dir Lib)]
extraDynLibFlavours :: BuildInfo -> [FilePath]
extraLibFlavours :: BuildInfo -> [FilePath]
extraBundledLibs :: BuildInfo -> [FilePath]
extraGHCiLibs :: BuildInfo -> [FilePath]
extraLibsStatic :: BuildInfo -> [FilePath]
extraLibs :: BuildInfo -> [FilePath]
oldExtensions :: BuildInfo -> [Extension]
otherExtensions :: BuildInfo -> [Extension]
defaultExtensions :: BuildInfo -> [Extension]
otherLanguages :: BuildInfo -> [Language]
defaultLanguage :: BuildInfo -> Maybe Language
autogenModules :: BuildInfo -> [ModuleName]
virtualModules :: BuildInfo -> [ModuleName]
otherModules :: BuildInfo -> [ModuleName]
hsSourceDirs :: BuildInfo -> [SymbolicPath Pkg ('Dir Source)]
jsSources :: BuildInfo -> [SymbolicPath Pkg 'File]
cxxSources :: BuildInfo -> [SymbolicPath Pkg 'File]
cSources :: BuildInfo -> [SymbolicPath Pkg 'File]
cmmSources :: BuildInfo -> [SymbolicPath Pkg 'File]
asmSources :: BuildInfo -> [SymbolicPath Pkg 'File]
extraFrameworkDirs :: BuildInfo -> [SymbolicPath Pkg ('Dir Framework)]
frameworks :: BuildInfo -> [RelativePath Framework 'File]
pkgconfigDepends :: BuildInfo -> [PkgconfigDependency]
hsc2hsOptions :: BuildInfo -> [FilePath]
ldOptions :: BuildInfo -> [FilePath]
cxxOptions :: BuildInfo -> [FilePath]
ccOptions :: BuildInfo -> [FilePath]
cmmOptions :: BuildInfo -> [FilePath]
asmOptions :: BuildInfo -> [FilePath]
cppOptions :: BuildInfo -> [FilePath]
buildToolDepends :: BuildInfo -> [ExeDependency]
buildTools :: BuildInfo -> [LegacyExeDependency]
buildable :: BuildInfo -> Bool
buildable :: Bool
buildTools :: [LegacyExeDependency]
buildToolDepends :: [ExeDependency]
cppOptions :: [FilePath]
asmOptions :: [FilePath]
cmmOptions :: [FilePath]
ccOptions :: [FilePath]
cxxOptions :: [FilePath]
ldOptions :: [FilePath]
hsc2hsOptions :: [FilePath]
pkgconfigDepends :: [PkgconfigDependency]
frameworks :: [RelativePath Framework 'File]
extraFrameworkDirs :: [SymbolicPath Pkg ('Dir Framework)]
asmSources :: [SymbolicPath Pkg 'File]
cmmSources :: [SymbolicPath Pkg 'File]
cSources :: [SymbolicPath Pkg 'File]
cxxSources :: [SymbolicPath Pkg 'File]
jsSources :: [SymbolicPath Pkg 'File]
hsSourceDirs :: [SymbolicPath Pkg ('Dir Source)]
otherModules :: [ModuleName]
virtualModules :: [ModuleName]
autogenModules :: [ModuleName]
defaultLanguage :: Maybe Language
otherLanguages :: [Language]
defaultExtensions :: [Extension]
otherExtensions :: [Extension]
oldExtensions :: [Extension]
extraLibs :: [FilePath]
extraLibsStatic :: [FilePath]
extraGHCiLibs :: [FilePath]
extraBundledLibs :: [FilePath]
extraLibFlavours :: [FilePath]
extraDynLibFlavours :: [FilePath]
extraLibDirs :: [SymbolicPath Pkg ('Dir Lib)]
extraLibDirsStatic :: [SymbolicPath Pkg ('Dir Lib)]
includeDirs :: [SymbolicPath Pkg ('Dir Include)]
includes :: [SymbolicPath Include 'File]
autogenIncludes :: [RelativePath Include 'File]
installIncludes :: [RelativePath Include 'File]
options :: PerCompilerFlavor [FilePath]
profOptions :: PerCompilerFlavor [FilePath]
sharedOptions :: PerCompilerFlavor [FilePath]
profSharedOptions :: PerCompilerFlavor [FilePath]
staticOptions :: PerCompilerFlavor [FilePath]
customFieldsBI :: [(FilePath, FilePath)]
targetBuildDepends :: [Dependency]
mixins :: [Mixin]
..} = (,([DynOption]
exts, [PackageName]
deps)) ([FilePath] -> ([FilePath], ([DynOption], [PackageName])))
-> [FilePath] -> ([FilePath], ([DynOption], [PackageName]))
forall a b. (a -> b) -> a -> b
$ do
FilePath
m <- [FilePath]
extraModules [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ (ModuleName -> FilePath
ModuleName.toFilePath (ModuleName -> FilePath) -> [ModuleName] -> [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ModuleName]
otherModules)
ShowS
normalise ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ShowS
takeDirectory FilePath
cabalFile </>) ShowS -> [FilePath] -> [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> [FilePath]
prependSrcDirs (ShowS
dropExtensions FilePath
m)
where
prependSrcDirs :: FilePath -> [FilePath]
prependSrcDirs FilePath
f
| [SymbolicPath Pkg ('Dir Source)] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [SymbolicPath Pkg ('Dir Source)]
hsSourceDirs = [FilePath
f]
| Bool
otherwise = (FilePath -> ShowS
</> FilePath
f) ShowS
-> (SymbolicPath Pkg ('Dir Source) -> FilePath)
-> SymbolicPath Pkg ('Dir Source)
-> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SymbolicPath Pkg ('Dir Source) -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath (SymbolicPath Pkg ('Dir Source) -> FilePath)
-> [SymbolicPath Pkg ('Dir Source)] -> [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [SymbolicPath Pkg ('Dir Source)]
hsSourceDirs
deps :: [PackageName]
deps = Dependency -> PackageName
depPkgName (Dependency -> PackageName) -> [Dependency] -> [PackageName]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Dependency]
targetBuildDepends
exts :: [DynOption]
exts = [DynOption]
-> (Language -> [DynOption]) -> Maybe Language -> [DynOption]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] Language -> [DynOption]
langExt Maybe Language
defaultLanguage [DynOption] -> [DynOption] -> [DynOption]
forall a. [a] -> [a] -> [a]
++ (Extension -> DynOption) -> [Extension] -> [DynOption]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Extension -> DynOption
extToDynOption [Extension]
defaultExtensions
langExt :: Language -> [DynOption]
langExt =
DynOption -> [DynOption]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DynOption -> [DynOption])
-> (Language -> DynOption) -> Language -> [DynOption]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> DynOption
DynOption (FilePath -> DynOption)
-> (Language -> FilePath) -> Language -> DynOption
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath
"-X" <>) ShowS -> (Language -> FilePath) -> Language -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
UnknownLanguage FilePath
lan -> FilePath
lan
Language
lan -> Language -> FilePath
forall a. Show a => a -> FilePath
show Language
lan
extToDynOption :: Extension -> DynOption
extToDynOption =
FilePath -> DynOption
DynOption (FilePath -> DynOption)
-> (Extension -> FilePath) -> Extension -> DynOption
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
EnableExtension KnownExtension
e -> FilePath
"-X" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ KnownExtension -> FilePath
forall a. Show a => a -> FilePath
show KnownExtension
e
DisableExtension KnownExtension
e -> FilePath
"-XNo" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ KnownExtension -> FilePath
forall a. Show a => a -> FilePath
show KnownExtension
e
UnknownExtension FilePath
e -> FilePath
"-X" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
e
extractFromLibrary :: Library -> ([FilePath], ([DynOption], [PackageName]))
extractFromLibrary Library {Bool
[ModuleName]
[ModuleReexport]
LibraryVisibility
LibraryName
BuildInfo
libBuildInfo :: Library -> BuildInfo
libVisibility :: Library -> LibraryVisibility
libExposed :: Library -> Bool
signatures :: Library -> [ModuleName]
reexportedModules :: Library -> [ModuleReexport]
exposedModules :: Library -> [ModuleName]
libName :: Library -> LibraryName
libName :: LibraryName
exposedModules :: [ModuleName]
reexportedModules :: [ModuleReexport]
signatures :: [ModuleName]
libExposed :: Bool
libVisibility :: LibraryVisibility
libBuildInfo :: BuildInfo
..} =
[FilePath]
-> BuildInfo -> ([FilePath], ([DynOption], [PackageName]))
extractFromBuildInfo (ModuleName -> FilePath
ModuleName.toFilePath (ModuleName -> FilePath) -> [ModuleName] -> [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ModuleName]
exposedModules) BuildInfo
libBuildInfo
extractFromExecutable :: Executable -> ([FilePath], ([DynOption], [PackageName]))
extractFromExecutable Executable {UnqualComponentName
ExecutableScope
RelativePath Source 'File
BuildInfo
buildInfo :: Executable -> BuildInfo
exeName :: UnqualComponentName
modulePath :: RelativePath Source 'File
exeScope :: ExecutableScope
buildInfo :: BuildInfo
exeScope :: Executable -> ExecutableScope
modulePath :: Executable -> RelativePath Source 'File
exeName :: Executable -> UnqualComponentName
..} =
[FilePath]
-> BuildInfo -> ([FilePath], ([DynOption], [PackageName]))
extractFromBuildInfo [RelativePath Source 'File -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath RelativePath Source 'File
modulePath] BuildInfo
buildInfo
extractFromTestSuite :: TestSuite -> ([FilePath], ([DynOption], [PackageName]))
extractFromTestSuite TestSuite {[FilePath]
UnqualComponentName
TestSuiteInterface
BuildInfo
testBuildInfo :: TestSuite -> BuildInfo
testName :: UnqualComponentName
testInterface :: TestSuiteInterface
testBuildInfo :: BuildInfo
testCodeGenerators :: [FilePath]
testCodeGenerators :: TestSuite -> [FilePath]
testInterface :: TestSuite -> TestSuiteInterface
testName :: TestSuite -> UnqualComponentName
..} =
[FilePath]
-> BuildInfo -> ([FilePath], ([DynOption], [PackageName]))
extractFromBuildInfo [FilePath]
mainPath BuildInfo
testBuildInfo
where
mainPath :: [FilePath]
mainPath = case TestSuiteInterface
testInterface of
TestSuiteExeV10 Version
_ RelativePath Source 'File
p -> [RelativePath Source 'File -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath RelativePath Source 'File
p]
TestSuiteLibV09 Version
_ ModuleName
p -> [ModuleName -> FilePath
ModuleName.toFilePath ModuleName
p]
TestSuiteUnsupported {} -> []
extractFromBenchmark :: Benchmark -> ([FilePath], ([DynOption], [PackageName]))
extractFromBenchmark Benchmark {UnqualComponentName
BenchmarkInterface
BuildInfo
benchmarkBuildInfo :: Benchmark -> BuildInfo
benchmarkName :: UnqualComponentName
benchmarkInterface :: BenchmarkInterface
benchmarkBuildInfo :: BuildInfo
benchmarkInterface :: Benchmark -> BenchmarkInterface
benchmarkName :: Benchmark -> UnqualComponentName
..} =
[FilePath]
-> BuildInfo -> ([FilePath], ([DynOption], [PackageName]))
extractFromBuildInfo [FilePath]
mainPath BuildInfo
benchmarkBuildInfo
where
mainPath :: [FilePath]
mainPath = case BenchmarkInterface
benchmarkInterface of
BenchmarkExeV10 Version
_ RelativePath Source 'File
p -> [RelativePath Source 'File -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath RelativePath Source 'File
p]
BenchmarkUnsupported {} -> []