{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE ViewPatterns #-}
module Ormolu.Utils.Cabal
( CabalInfo (..),
defaultCabalInfo,
PackageName,
unPackageName,
Extension (..),
getCabalInfoForSourceFile,
findCabalFile,
parseCabalInfo,
)
where
import Control.Exception
import Control.Monad.IO.Class
import qualified Data.ByteString as B
import Data.IORef
import Data.Map.Lazy (Map)
import qualified Data.Map.Lazy as M
import Data.Maybe (maybeToList)
import Data.Set (Set)
import qualified Data.Set as Set
import qualified Distribution.ModuleName as ModuleName
import Distribution.PackageDescription
import Distribution.PackageDescription.Parsec
import qualified Distribution.Types.CondTree as CT
import Distribution.Utils.Path (getSymbolicPath)
import Language.Haskell.Extension
import Ormolu.Config
import Ormolu.Exception
import System.Directory
import System.FilePath
import System.IO (hPutStrLn, stderr)
import System.IO.Error (isDoesNotExistError)
import System.IO.Unsafe (unsafePerformIO)
data CabalInfo = CabalInfo
{
CabalInfo -> Maybe FilePath
ciPackageName :: !(Maybe String),
CabalInfo -> [DynOption]
ciDynOpts :: ![DynOption],
CabalInfo -> Set FilePath
ciDependencies :: !(Set String),
CabalInfo -> Maybe FilePath
ciCabalFilePath :: !(Maybe FilePath)
}
deriving (CabalInfo -> CabalInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CabalInfo -> CabalInfo -> Bool
$c/= :: CabalInfo -> CabalInfo -> Bool
== :: CabalInfo -> CabalInfo -> Bool
$c== :: CabalInfo -> CabalInfo -> Bool
Eq, Int -> CabalInfo -> ShowS
[CabalInfo] -> ShowS
CabalInfo -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [CabalInfo] -> ShowS
$cshowList :: [CabalInfo] -> ShowS
show :: CabalInfo -> FilePath
$cshow :: CabalInfo -> FilePath
showsPrec :: Int -> CabalInfo -> ShowS
$cshowsPrec :: Int -> CabalInfo -> ShowS
Show)
defaultCabalInfo :: CabalInfo
defaultCabalInfo :: CabalInfo
defaultCabalInfo =
CabalInfo
{ ciPackageName :: Maybe FilePath
ciPackageName = forall a. Maybe a
Nothing,
ciDynOpts :: [DynOption]
ciDynOpts = [],
ciDependencies :: Set FilePath
ciDependencies = forall a. Set a
Set.empty,
ciCabalFilePath :: Maybe FilePath
ciCabalFilePath = forall a. Maybe a
Nothing
}
getCabalInfoForSourceFile ::
MonadIO m =>
FilePath ->
m CabalInfo
getCabalInfoForSourceFile :: forall (m :: * -> *). MonadIO m => FilePath -> m CabalInfo
getCabalInfoForSourceFile FilePath
sourceFile = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
forall (m :: * -> *). MonadIO m => FilePath -> m (Maybe FilePath)
findCabalFile FilePath
sourceFile forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Just FilePath
cabalFile -> forall (m :: * -> *).
MonadIO m =>
FilePath -> FilePath -> m CabalInfo
parseCabalInfo FilePath
cabalFile FilePath
sourceFile
Maybe FilePath
Nothing -> do
Handle -> FilePath -> IO ()
hPutStrLn Handle
stderr forall a b. (a -> b) -> a -> b
$ FilePath
"Could not find a .cabal file for " forall a. Semigroup a => a -> a -> a
<> FilePath
sourceFile
forall (m :: * -> *) a. Monad m => a -> m a
return CabalInfo
defaultCabalInfo
findCabalFile ::
MonadIO m =>
FilePath ->
m (Maybe FilePath)
findCabalFile :: forall (m :: * -> *). MonadIO m => FilePath -> m (Maybe FilePath)
findCabalFile FilePath
sourceFile = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
FilePath
parentDir <- ShowS
takeDirectory forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> IO FilePath
makeAbsolute FilePath
sourceFile
[FilePath]
dirEntries <-
FilePath -> IO [FilePath]
listDirectory FilePath
parentDir forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catch` \case
(IOError -> Bool
isDoesNotExistError -> Bool
True) -> forall (f :: * -> *) a. Applicative f => a -> f a
pure []
IOError
e -> forall e a. Exception e => e -> IO a
throwIO IOError
e
let findDotCabal :: [FilePath] -> IO (Maybe FilePath)
findDotCabal = \case
[] -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
FilePath
e : [FilePath]
es
| ShowS
takeExtension FilePath
e forall a. Eq a => a -> a -> Bool
== FilePath
".cabal" ->
FilePath -> IO Bool
doesFileExist (FilePath
parentDir FilePath -> ShowS
</> FilePath
e) forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Bool
True -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just FilePath
e
Bool
False -> [FilePath] -> IO (Maybe FilePath)
findDotCabal [FilePath]
es
FilePath
_ : [FilePath]
es -> [FilePath] -> IO (Maybe FilePath)
findDotCabal [FilePath]
es
[FilePath] -> IO (Maybe FilePath)
findDotCabal [FilePath]
dirEntries forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Just FilePath
cabalFile -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ FilePath
parentDir FilePath -> ShowS
</> FilePath
cabalFile
Maybe FilePath
Nothing ->
if FilePath -> Bool
isDrive FilePath
parentDir
then forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
else forall (m :: * -> *). MonadIO m => FilePath -> m (Maybe FilePath)
findCabalFile FilePath
parentDir
data CachedCabalFile = CachedCabalFile
{
CachedCabalFile -> GenericPackageDescription
genericPackageDescription :: GenericPackageDescription,
CachedCabalFile -> Map FilePath ([DynOption], [FilePath])
extensionsAndDeps :: Map FilePath ([DynOption], [String])
}
deriving (Int -> CachedCabalFile -> ShowS
[CachedCabalFile] -> ShowS
CachedCabalFile -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [CachedCabalFile] -> ShowS
$cshowList :: [CachedCabalFile] -> ShowS
show :: CachedCabalFile -> FilePath
$cshow :: CachedCabalFile -> FilePath
showsPrec :: Int -> CachedCabalFile -> ShowS
$cshowsPrec :: Int -> CachedCabalFile -> ShowS
Show)
cabalCacheRef :: IORef (Map FilePath CachedCabalFile)
cabalCacheRef :: IORef (Map FilePath CachedCabalFile)
cabalCacheRef = forall a. IO a -> a
unsafePerformIO forall a b. (a -> b) -> a -> b
$ forall a. a -> IO (IORef a)
newIORef forall k a. Map k a
M.empty
{-# NOINLINE cabalCacheRef #-}
parseCabalInfo ::
MonadIO m =>
FilePath ->
FilePath ->
m CabalInfo
parseCabalInfo :: forall (m :: * -> *).
MonadIO m =>
FilePath -> FilePath -> m CabalInfo
parseCabalInfo FilePath
cabalFileAsGiven FilePath
sourceFileAsGiven = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
FilePath
cabalFile <- FilePath -> IO FilePath
makeAbsolute FilePath
cabalFileAsGiven
FilePath
sourceFileAbs <- FilePath -> IO FilePath
makeAbsolute FilePath
sourceFileAsGiven
Map FilePath CachedCabalFile
cabalCache <- forall a. IORef a -> IO a
readIORef IORef (Map FilePath CachedCabalFile)
cabalCacheRef
CachedCabalFile {GenericPackageDescription
Map FilePath ([DynOption], [FilePath])
extensionsAndDeps :: Map FilePath ([DynOption], [FilePath])
genericPackageDescription :: GenericPackageDescription
extensionsAndDeps :: CachedCabalFile -> Map FilePath ([DynOption], [FilePath])
genericPackageDescription :: CachedCabalFile -> GenericPackageDescription
..} <- forall (m :: * -> *) a. Monad m => Maybe a -> m a -> m a
whenNothing (forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup FilePath
cabalFile Map FilePath CachedCabalFile
cabalCache) forall a b. (a -> b) -> a -> b
$ do
ByteString
cabalFileBs <- FilePath -> IO ByteString
B.readFile FilePath
cabalFile
GenericPackageDescription
genericPackageDescription <-
forall (m :: * -> *) a. Monad m => Maybe a -> m a -> m a
whenNothing (ByteString -> Maybe GenericPackageDescription
parseGenericPackageDescriptionMaybe ByteString
cabalFileBs) forall a b. (a -> b) -> a -> b
$
forall e a. Exception e => e -> IO a
throwIO (FilePath -> OrmoluException
OrmoluCabalFileParsingFailed FilePath
cabalFile)
let extensionsAndDeps :: Map FilePath ([DynOption], [FilePath])
extensionsAndDeps =
FilePath
-> GenericPackageDescription
-> Map FilePath ([DynOption], [FilePath])
getExtensionAndDepsMap FilePath
cabalFile GenericPackageDescription
genericPackageDescription
cachedCabalFile :: CachedCabalFile
cachedCabalFile = CachedCabalFile {GenericPackageDescription
Map FilePath ([DynOption], [FilePath])
extensionsAndDeps :: Map FilePath ([DynOption], [FilePath])
genericPackageDescription :: GenericPackageDescription
extensionsAndDeps :: Map FilePath ([DynOption], [FilePath])
genericPackageDescription :: GenericPackageDescription
..}
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef IORef (Map FilePath CachedCabalFile)
cabalCacheRef forall a b. (a -> b) -> a -> b
$
(,CachedCabalFile
cachedCabalFile) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert FilePath
cabalFile CachedCabalFile
cachedCabalFile
([DynOption]
dynOpts, [FilePath]
dependencies) <-
forall (m :: * -> *) a. Monad m => Maybe a -> m a -> m a
whenNothing (forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (ShowS
dropExtensions FilePath
sourceFileAbs) Map FilePath ([DynOption], [FilePath])
extensionsAndDeps) forall a b. (a -> b) -> a -> b
$ do
FilePath
relativeCabalFile <- FilePath -> IO FilePath
makeRelativeToCurrentDirectory FilePath
cabalFile
Handle -> FilePath -> IO ()
hPutStrLn Handle
stderr forall a b. (a -> b) -> a -> b
$
FilePath
"Found .cabal file "
forall a. Semigroup a => a -> a -> a
<> FilePath
relativeCabalFile
forall a. Semigroup a => a -> a -> a
<> FilePath
", but it did not mention "
forall a. Semigroup a => a -> a -> a
<> FilePath
sourceFileAsGiven
forall (m :: * -> *) a. Monad m => a -> m a
return ([], [])
let pdesc :: PackageDescription
pdesc = GenericPackageDescription -> PackageDescription
packageDescription GenericPackageDescription
genericPackageDescription
packageName :: FilePath
packageName = (PackageName -> FilePath
unPackageName forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageIdentifier -> PackageName
pkgName forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageDescription -> PackageIdentifier
package) PackageDescription
pdesc
forall (m :: * -> *) a. Monad m => a -> m a
return
CabalInfo
{ ciPackageName :: Maybe FilePath
ciPackageName = forall a. a -> Maybe a
Just FilePath
packageName,
ciDynOpts :: [DynOption]
ciDynOpts = [DynOption]
dynOpts,
ciDependencies :: Set FilePath
ciDependencies = forall a. Ord a => [a] -> Set a
Set.fromList [FilePath]
dependencies,
ciCabalFilePath :: Maybe FilePath
ciCabalFilePath = forall a. a -> Maybe a
Just FilePath
cabalFile
}
where
whenNothing :: Monad m => Maybe a -> m a -> m a
whenNothing :: forall (m :: * -> *) a. Monad m => Maybe a -> m a -> m a
whenNothing Maybe a
maya m a
ma = forall b a. b -> (a -> b) -> Maybe a -> b
maybe m a
ma forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe a
maya
getExtensionAndDepsMap ::
FilePath ->
GenericPackageDescription ->
Map FilePath ([DynOption], [String])
getExtensionAndDepsMap :: FilePath
-> GenericPackageDescription
-> Map FilePath ([DynOption], [FilePath])
getExtensionAndDepsMap FilePath
cabalFile GenericPackageDescription {[(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
[(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
[(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
[(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
[(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
[PackageFlag]
Maybe Version
Maybe (CondTree ConfVar [Dependency] Library)
PackageDescription
condBenchmarks :: GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
condExecutables :: GenericPackageDescription
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
condForeignLibs :: GenericPackageDescription
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] ForeignLib)]
condLibrary :: GenericPackageDescription
-> Maybe (CondTree ConfVar [Dependency] Library)
condSubLibraries :: GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
condTestSuites :: GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
genPackageFlags :: GenericPackageDescription -> [PackageFlag]
gpdScannedVersion :: GenericPackageDescription -> Maybe Version
condBenchmarks :: [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
condTestSuites :: [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
condExecutables :: [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
condForeignLibs :: [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
condSubLibraries :: [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
condLibrary :: Maybe (CondTree ConfVar [Dependency] Library)
genPackageFlags :: [PackageFlag]
gpdScannedVersion :: Maybe Version
packageDescription :: PackageDescription
packageDescription :: GenericPackageDescription -> PackageDescription
..} =
forall (f :: * -> *) k a.
(Foldable f, Ord k) =>
f (Map k a) -> Map k a
M.unions forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$
[ 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], [FilePath]))
extractFromLibrary forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [CondTree ConfVar [Dependency] Library]
lib forall a. [a] -> [a] -> [a]
++ [CondTree ConfVar [Dependency] Library]
sublibs,
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], [FilePath]))
extractFromExecutable forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> b
snd forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
condExecutables,
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], [FilePath]))
extractFromTestSuite forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> b
snd forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
condTestSuites,
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], [FilePath]))
extractFromBenchmark forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> b
snd 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 = forall a. Maybe a -> [a]
maybeToList Maybe (CondTree ConfVar [Dependency] Library)
condLibrary
sublibs :: [CondTree ConfVar [Dependency] Library]
sublibs = forall a b. (a, b) -> b
snd 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 = forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ((,a
extsAndDeps) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [k]
files)
where
(a
mergedA, 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], [FilePath]))
extractFromBuildInfo [FilePath]
extraModules BuildInfo {Bool
[FilePath]
[(FilePath, FilePath)]
[Language]
[Extension]
[Dependency]
[ExeDependency]
[LegacyExeDependency]
[Mixin]
[ModuleName]
[PkgconfigDependency]
[SymbolicPath PackageDir SourceDir]
Maybe Language
PerCompilerFlavor [FilePath]
asmOptions :: BuildInfo -> [FilePath]
asmSources :: BuildInfo -> [FilePath]
autogenIncludes :: BuildInfo -> [FilePath]
autogenModules :: BuildInfo -> [ModuleName]
buildToolDepends :: BuildInfo -> [ExeDependency]
buildTools :: BuildInfo -> [LegacyExeDependency]
buildable :: BuildInfo -> Bool
cSources :: BuildInfo -> [FilePath]
ccOptions :: BuildInfo -> [FilePath]
cmmOptions :: BuildInfo -> [FilePath]
cmmSources :: BuildInfo -> [FilePath]
cppOptions :: BuildInfo -> [FilePath]
customFieldsBI :: BuildInfo -> [(FilePath, FilePath)]
cxxOptions :: BuildInfo -> [FilePath]
cxxSources :: BuildInfo -> [FilePath]
defaultExtensions :: BuildInfo -> [Extension]
defaultLanguage :: BuildInfo -> Maybe Language
extraBundledLibs :: BuildInfo -> [FilePath]
extraDynLibFlavours :: BuildInfo -> [FilePath]
extraFrameworkDirs :: BuildInfo -> [FilePath]
extraGHCiLibs :: BuildInfo -> [FilePath]
extraLibDirs :: BuildInfo -> [FilePath]
extraLibFlavours :: BuildInfo -> [FilePath]
extraLibs :: BuildInfo -> [FilePath]
frameworks :: BuildInfo -> [FilePath]
hsSourceDirs :: BuildInfo -> [SymbolicPath PackageDir SourceDir]
hsc2hsOptions :: BuildInfo -> [FilePath]
includeDirs :: BuildInfo -> [FilePath]
includes :: BuildInfo -> [FilePath]
installIncludes :: BuildInfo -> [FilePath]
jsSources :: BuildInfo -> [FilePath]
ldOptions :: BuildInfo -> [FilePath]
mixins :: BuildInfo -> [Mixin]
oldExtensions :: BuildInfo -> [Extension]
options :: BuildInfo -> PerCompilerFlavor [FilePath]
otherExtensions :: BuildInfo -> [Extension]
otherLanguages :: BuildInfo -> [Language]
otherModules :: BuildInfo -> [ModuleName]
pkgconfigDepends :: BuildInfo -> [PkgconfigDependency]
profOptions :: BuildInfo -> PerCompilerFlavor [FilePath]
sharedOptions :: BuildInfo -> PerCompilerFlavor [FilePath]
staticOptions :: BuildInfo -> PerCompilerFlavor [FilePath]
targetBuildDepends :: BuildInfo -> [Dependency]
virtualModules :: BuildInfo -> [ModuleName]
mixins :: [Mixin]
targetBuildDepends :: [Dependency]
customFieldsBI :: [(FilePath, FilePath)]
staticOptions :: PerCompilerFlavor [FilePath]
sharedOptions :: PerCompilerFlavor [FilePath]
profOptions :: PerCompilerFlavor [FilePath]
options :: PerCompilerFlavor [FilePath]
installIncludes :: [FilePath]
autogenIncludes :: [FilePath]
includes :: [FilePath]
includeDirs :: [FilePath]
extraLibDirs :: [FilePath]
extraDynLibFlavours :: [FilePath]
extraLibFlavours :: [FilePath]
extraBundledLibs :: [FilePath]
extraGHCiLibs :: [FilePath]
extraLibs :: [FilePath]
oldExtensions :: [Extension]
otherExtensions :: [Extension]
defaultExtensions :: [Extension]
otherLanguages :: [Language]
defaultLanguage :: Maybe Language
autogenModules :: [ModuleName]
virtualModules :: [ModuleName]
otherModules :: [ModuleName]
hsSourceDirs :: [SymbolicPath PackageDir SourceDir]
jsSources :: [FilePath]
cxxSources :: [FilePath]
cSources :: [FilePath]
cmmSources :: [FilePath]
asmSources :: [FilePath]
extraFrameworkDirs :: [FilePath]
frameworks :: [FilePath]
pkgconfigDepends :: [PkgconfigDependency]
hsc2hsOptions :: [FilePath]
ldOptions :: [FilePath]
cxxOptions :: [FilePath]
ccOptions :: [FilePath]
cmmOptions :: [FilePath]
asmOptions :: [FilePath]
cppOptions :: [FilePath]
buildToolDepends :: [ExeDependency]
buildTools :: [LegacyExeDependency]
buildable :: Bool
..} = (,([DynOption]
exts, [FilePath]
deps)) forall a b. (a -> b) -> a -> b
$ do
FilePath
m <- [FilePath]
extraModules forall a. [a] -> [a] -> [a]
++ (ModuleName -> FilePath
ModuleName.toFilePath forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ModuleName]
otherModules)
ShowS
normalise forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ShowS
takeDirectory FilePath
cabalFile FilePath -> ShowS
</>) 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
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null [SymbolicPath PackageDir SourceDir]
hsSourceDirs = [FilePath
f]
| Bool
otherwise = (FilePath -> ShowS
</> FilePath
f) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall from to. SymbolicPath from to -> FilePath
getSymbolicPath forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [SymbolicPath PackageDir SourceDir]
hsSourceDirs
deps :: [FilePath]
deps = PackageName -> FilePath
unPackageName forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dependency -> PackageName
depPkgName forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Dependency]
targetBuildDepends
exts :: [DynOption]
exts = forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] Language -> [DynOption]
langExt Maybe Language
defaultLanguage forall a. [a] -> [a] -> [a]
++ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Extension -> DynOption
extToDynOption [Extension]
defaultExtensions
langExt :: Language -> [DynOption]
langExt =
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> DynOption
DynOption forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath
"-X" forall a. Semigroup a => a -> a -> a
<>) forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
UnknownLanguage FilePath
lan -> FilePath
lan
Language
lan -> forall a. Show a => a -> FilePath
show Language
lan
extToDynOption :: Extension -> DynOption
extToDynOption =
FilePath -> DynOption
DynOption forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
EnableExtension KnownExtension
e -> FilePath
"-X" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show KnownExtension
e
DisableExtension KnownExtension
e -> FilePath
"-XNo" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show KnownExtension
e
UnknownExtension FilePath
e -> FilePath
"-X" forall a. [a] -> [a] -> [a]
++ FilePath
e
extractFromLibrary :: Library -> ([FilePath], ([DynOption], [FilePath]))
extractFromLibrary Library {Bool
[ModuleReexport]
[ModuleName]
BuildInfo
LibraryName
LibraryVisibility
exposedModules :: Library -> [ModuleName]
libBuildInfo :: Library -> BuildInfo
libExposed :: Library -> Bool
libName :: Library -> LibraryName
libVisibility :: Library -> LibraryVisibility
reexportedModules :: Library -> [ModuleReexport]
signatures :: Library -> [ModuleName]
libBuildInfo :: BuildInfo
libVisibility :: LibraryVisibility
libExposed :: Bool
signatures :: [ModuleName]
reexportedModules :: [ModuleReexport]
exposedModules :: [ModuleName]
libName :: LibraryName
..} =
[FilePath] -> BuildInfo -> ([FilePath], ([DynOption], [FilePath]))
extractFromBuildInfo (ModuleName -> FilePath
ModuleName.toFilePath forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ModuleName]
exposedModules) BuildInfo
libBuildInfo
extractFromExecutable :: Executable -> ([FilePath], ([DynOption], [FilePath]))
extractFromExecutable Executable {FilePath
BuildInfo
ExecutableScope
UnqualComponentName
buildInfo :: Executable -> BuildInfo
exeName :: Executable -> UnqualComponentName
exeScope :: Executable -> ExecutableScope
modulePath :: Executable -> FilePath
buildInfo :: BuildInfo
exeScope :: ExecutableScope
modulePath :: FilePath
exeName :: UnqualComponentName
..} =
[FilePath] -> BuildInfo -> ([FilePath], ([DynOption], [FilePath]))
extractFromBuildInfo [FilePath
modulePath] BuildInfo
buildInfo
extractFromTestSuite :: TestSuite -> ([FilePath], ([DynOption], [FilePath]))
extractFromTestSuite TestSuite {BuildInfo
TestSuiteInterface
UnqualComponentName
testBuildInfo :: TestSuite -> BuildInfo
testInterface :: TestSuite -> TestSuiteInterface
testName :: TestSuite -> UnqualComponentName
testBuildInfo :: BuildInfo
testInterface :: TestSuiteInterface
testName :: UnqualComponentName
..} =
[FilePath] -> BuildInfo -> ([FilePath], ([DynOption], [FilePath]))
extractFromBuildInfo [FilePath]
mainPath BuildInfo
testBuildInfo
where
mainPath :: [FilePath]
mainPath = case TestSuiteInterface
testInterface of
TestSuiteExeV10 Version
_ FilePath
p -> [FilePath
p]
TestSuiteLibV09 Version
_ ModuleName
p -> [ModuleName -> FilePath
ModuleName.toFilePath ModuleName
p]
TestSuiteUnsupported {} -> []
extractFromBenchmark :: Benchmark -> ([FilePath], ([DynOption], [FilePath]))
extractFromBenchmark Benchmark {BuildInfo
BenchmarkInterface
UnqualComponentName
benchmarkBuildInfo :: Benchmark -> BuildInfo
benchmarkInterface :: Benchmark -> BenchmarkInterface
benchmarkName :: Benchmark -> UnqualComponentName
benchmarkBuildInfo :: BuildInfo
benchmarkInterface :: BenchmarkInterface
benchmarkName :: UnqualComponentName
..} =
[FilePath] -> BuildInfo -> ([FilePath], ([DynOption], [FilePath]))
extractFromBuildInfo [FilePath]
mainPath BuildInfo
benchmarkBuildInfo
where
mainPath :: [FilePath]
mainPath = case BenchmarkInterface
benchmarkInterface of
BenchmarkExeV10 Version
_ FilePath
p -> [FilePath
p]
BenchmarkUnsupported {} -> []