{-# 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.IORef
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 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 (findClosestFileSatisfying, withIORefCache)
import System.Directory
import System.FilePath
import System.IO.Unsafe (unsafePerformIO)

-- | The result of searching for a @.cabal@ file.
--
-- @since 0.5.3.0
data CabalSearchResult
  = -- | Cabal file could not be found
    CabalNotFound
  | -- | Cabal file was found, but it did not mention the source file in
    -- question
    CabalDidNotMention CabalInfo
  | -- | Cabal file was found and it mentions the source file in question
    CabalFound CabalInfo
  deriving (CabalSearchResult -> CabalSearchResult -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CabalSearchResult -> CabalSearchResult -> Bool
$c/= :: CabalSearchResult -> CabalSearchResult -> Bool
== :: CabalSearchResult -> CabalSearchResult -> Bool
$c== :: CabalSearchResult -> CabalSearchResult -> Bool
Eq, Int -> CabalSearchResult -> ShowS
[CabalSearchResult] -> ShowS
CabalSearchResult -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [CabalSearchResult] -> ShowS
$cshowList :: [CabalSearchResult] -> ShowS
show :: CabalSearchResult -> FilePath
$cshow :: CabalSearchResult -> FilePath
showsPrec :: Int -> CabalSearchResult -> ShowS
$cshowsPrec :: Int -> CabalSearchResult -> ShowS
Show)

-- | Cabal information of interest to Ormolu.
data CabalInfo = CabalInfo
  { -- | Package name
    CabalInfo -> PackageName
ciPackageName :: !PackageName,
    -- | Extension and language settings in the form of 'DynOption's
    CabalInfo -> [DynOption]
ciDynOpts :: ![DynOption],
    -- | Direct dependencies
    CabalInfo -> Set PackageName
ciDependencies :: !(Set PackageName),
    -- | Absolute path to the cabal file
    CabalInfo -> FilePath
ciCabalFilePath :: !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)

-- | Locate a @.cabal@ file corresponding to the given Haskell source file
-- and obtain 'CabalInfo' from it.
getCabalInfoForSourceFile ::
  (MonadIO m) =>
  -- | Haskell source file
  FilePath ->
  -- | Extracted cabal info, if any
  m CabalSearchResult
getCabalInfoForSourceFile :: forall (m :: * -> *). MonadIO m => FilePath -> m CabalSearchResult
getCabalInfoForSourceFile FilePath
sourceFile =
  forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (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 -> do
      (Bool
mentioned, CabalInfo
cabalInfo) <- forall (m :: * -> *).
MonadIO m =>
FilePath -> FilePath -> m (Bool, CabalInfo)
parseCabalInfo FilePath
cabalFile FilePath
sourceFile
      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 -> forall (m :: * -> *) a. Monad m => a -> m a
return CabalSearchResult
CabalNotFound

-- | Find the path to an appropriate @.cabal@ file for a Haskell source
-- file, if available.
findCabalFile ::
  (MonadIO m) =>
  -- | Path to a Haskell source file in a project with a @.cabal@ file
  FilePath ->
  -- | Absolute path to the @.cabal@ file, if available
  m (Maybe FilePath)
findCabalFile :: forall (m :: * -> *). MonadIO m => FilePath -> m (Maybe FilePath)
findCabalFile = forall (m :: * -> *).
MonadIO m =>
(FilePath -> Bool) -> FilePath -> m (Maybe FilePath)
findClosestFileSatisfying forall a b. (a -> b) -> a -> b
$ \FilePath
x ->
  ShowS
takeExtension FilePath
x forall a. Eq a => a -> a -> Bool
== FilePath
".cabal"

-- | Parsed cabal file information to be shared across multiple source files.
data CachedCabalFile = CachedCabalFile
  { -- | Parsed generic package description.
    CachedCabalFile -> GenericPackageDescription
genericPackageDescription :: GenericPackageDescription,
    -- | Map from Haskell source file paths (without any extensions) to the
    -- corresponding 'DynOption's and dependencies.
    CachedCabalFile -> Map FilePath ([DynOption], [PackageName])
extensionsAndDeps :: Map FilePath ([DynOption], [PackageName])
  }
  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)

-- | Cache ref that stores 'CachedCabalFile' per Cabal file.
cacheRef :: IORef (Map FilePath CachedCabalFile)
cacheRef :: IORef (Map FilePath CachedCabalFile)
cacheRef = 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 cacheRef #-}

-- | Parse 'CabalInfo' from a @.cabal@ file at the given 'FilePath'.
parseCabalInfo ::
  (MonadIO m) =>
  -- | Location of the .cabal file
  FilePath ->
  -- | Location of the source file we are formatting
  FilePath ->
  -- | Indication if the source file was mentioned in the Cabal file and the
  -- extracted 'CabalInfo'
  m (Bool, CabalInfo)
parseCabalInfo :: forall (m :: * -> *).
MonadIO m =>
FilePath -> FilePath -> m (Bool, 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
  CachedCabalFile {GenericPackageDescription
Map FilePath ([DynOption], [PackageName])
extensionsAndDeps :: Map FilePath ([DynOption], [PackageName])
genericPackageDescription :: GenericPackageDescription
extensionsAndDeps :: CachedCabalFile -> Map FilePath ([DynOption], [PackageName])
genericPackageDescription :: CachedCabalFile -> GenericPackageDescription
..} <- forall k v. Ord k => IORef (Map k v) -> k -> IO v -> IO v
withIORefCache IORef (Map FilePath CachedCabalFile)
cacheRef FilePath
cabalFile forall a b. (a -> b) -> a -> b
$ do
    ByteString
cabalFileBs <- FilePath -> IO ByteString
B.readFile FilePath
cabalFile
    GenericPackageDescription
genericPackageDescription <-
      forall (f :: * -> *) e a.
Applicative f =>
Either e a -> (e -> f a) -> f a
whenLeft (forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
ParseResult a
-> ([PWarning], Either (Maybe Version, NonEmpty PError) a)
runParseResult forall a b. (a -> b) -> a -> b
$ ByteString -> ParseResult GenericPackageDescription
parseGenericPackageDescription ByteString
cabalFileBs) forall a b. (a -> b) -> a -> b
$
        forall e a. Exception e => e -> IO a
throwIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> NonEmpty PError -> OrmoluException
OrmoluCabalFileParsingFailed FilePath
cabalFile forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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
    forall (f :: * -> *) a. Applicative f => a -> f a
pure CachedCabalFile {GenericPackageDescription
Map FilePath ([DynOption], [PackageName])
extensionsAndDeps :: Map FilePath ([DynOption], [PackageName])
genericPackageDescription :: GenericPackageDescription
extensionsAndDeps :: Map FilePath ([DynOption], [PackageName])
genericPackageDescription :: GenericPackageDescription
..}
  let ([DynOption]
dynOpts, [PackageName]
dependencies, Bool
mentioned) =
        case 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 -> ([], 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
  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 = forall a. Ord a => [a] -> Set a
Set.fromList [PackageName]
dependencies,
          ciCabalFilePath :: FilePath
ciCabalFilePath = FilePath
cabalFile
        }
    )
  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 = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either e -> f a
ma forall (f :: * -> *) a. Applicative f => a -> f a
pure Either e a
eitha

-- | Get a map from Haskell source file paths (without any extensions) to
-- the corresponding 'DynOption's and dependencies.
getExtensionAndDepsMap ::
  -- | Path to the cabal file
  FilePath ->
  -- | Parsed generic package description
  GenericPackageDescription ->
  Map FilePath ([DynOption], [PackageName])
getExtensionAndDepsMap :: FilePath
-> GenericPackageDescription
-> Map FilePath ([DynOption], [PackageName])
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
gpdScannedVersion :: GenericPackageDescription -> Maybe Version
genPackageFlags :: GenericPackageDescription -> [PackageFlag]
condLibrary :: GenericPackageDescription
-> Maybe (CondTree ConfVar [Dependency] Library)
condSubLibraries :: GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
condForeignLibs :: GenericPackageDescription
-> [(UnqualComponentName,
     CondTree ConfVar [Dependency] ForeignLib)]
condExecutables :: GenericPackageDescription
-> [(UnqualComponentName,
     CondTree ConfVar [Dependency] Executable)]
condTestSuites :: GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
condBenchmarks :: GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
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], [PackageName]))
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], [PackageName]))
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], [PackageName]))
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], [PackageName]))
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], [PackageName]))
extractFromBuildInfo [FilePath]
extraModules BuildInfo {Bool
[FilePath]
[(FilePath, FilePath)]
[Language]
[Extension]
[Dependency]
[ExeDependency]
[LegacyExeDependency]
[Mixin]
[ModuleName]
[PkgconfigDependency]
[SymbolicPath PackageDir SourceDir]
Maybe Language
PerCompilerFlavor [FilePath]
buildable :: BuildInfo -> Bool
buildTools :: BuildInfo -> [LegacyExeDependency]
buildToolDepends :: BuildInfo -> [ExeDependency]
cppOptions :: BuildInfo -> [FilePath]
asmOptions :: BuildInfo -> [FilePath]
cmmOptions :: BuildInfo -> [FilePath]
ccOptions :: BuildInfo -> [FilePath]
cxxOptions :: BuildInfo -> [FilePath]
ldOptions :: BuildInfo -> [FilePath]
hsc2hsOptions :: BuildInfo -> [FilePath]
pkgconfigDepends :: BuildInfo -> [PkgconfigDependency]
frameworks :: BuildInfo -> [FilePath]
extraFrameworkDirs :: BuildInfo -> [FilePath]
asmSources :: BuildInfo -> [FilePath]
cmmSources :: BuildInfo -> [FilePath]
cSources :: BuildInfo -> [FilePath]
cxxSources :: BuildInfo -> [FilePath]
jsSources :: BuildInfo -> [FilePath]
hsSourceDirs :: BuildInfo -> [SymbolicPath PackageDir SourceDir]
otherModules :: BuildInfo -> [ModuleName]
virtualModules :: BuildInfo -> [ModuleName]
autogenModules :: BuildInfo -> [ModuleName]
defaultLanguage :: BuildInfo -> Maybe Language
otherLanguages :: BuildInfo -> [Language]
defaultExtensions :: BuildInfo -> [Extension]
otherExtensions :: BuildInfo -> [Extension]
oldExtensions :: BuildInfo -> [Extension]
extraLibs :: BuildInfo -> [FilePath]
extraLibsStatic :: BuildInfo -> [FilePath]
extraGHCiLibs :: BuildInfo -> [FilePath]
extraBundledLibs :: BuildInfo -> [FilePath]
extraLibFlavours :: BuildInfo -> [FilePath]
extraDynLibFlavours :: BuildInfo -> [FilePath]
extraLibDirs :: BuildInfo -> [FilePath]
extraLibDirsStatic :: BuildInfo -> [FilePath]
includeDirs :: BuildInfo -> [FilePath]
includes :: BuildInfo -> [FilePath]
autogenIncludes :: BuildInfo -> [FilePath]
installIncludes :: BuildInfo -> [FilePath]
options :: BuildInfo -> PerCompilerFlavor [FilePath]
profOptions :: BuildInfo -> PerCompilerFlavor [FilePath]
sharedOptions :: BuildInfo -> PerCompilerFlavor [FilePath]
staticOptions :: BuildInfo -> PerCompilerFlavor [FilePath]
customFieldsBI :: BuildInfo -> [(FilePath, FilePath)]
targetBuildDepends :: BuildInfo -> [Dependency]
mixins :: BuildInfo -> [Mixin]
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]
extraLibDirsStatic :: [FilePath]
extraLibDirs :: [FilePath]
extraDynLibFlavours :: [FilePath]
extraLibFlavours :: [FilePath]
extraBundledLibs :: [FilePath]
extraGHCiLibs :: [FilePath]
extraLibsStatic :: [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, [PackageName]
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 </>) 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 :: [PackageName]
deps = 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 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], [PackageName]))
extractFromLibrary Library {Bool
[ModuleReexport]
[ModuleName]
BuildInfo
LibraryName
LibraryVisibility
libName :: Library -> LibraryName
exposedModules :: Library -> [ModuleName]
reexportedModules :: Library -> [ModuleReexport]
signatures :: Library -> [ModuleName]
libExposed :: Library -> Bool
libVisibility :: Library -> LibraryVisibility
libBuildInfo :: Library -> BuildInfo
libBuildInfo :: BuildInfo
libVisibility :: LibraryVisibility
libExposed :: Bool
signatures :: [ModuleName]
reexportedModules :: [ModuleReexport]
exposedModules :: [ModuleName]
libName :: LibraryName
..} =
      [FilePath]
-> BuildInfo -> ([FilePath], ([DynOption], [PackageName]))
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], [PackageName]))
extractFromExecutable Executable {FilePath
BuildInfo
ExecutableScope
UnqualComponentName
exeName :: Executable -> UnqualComponentName
modulePath :: Executable -> FilePath
exeScope :: Executable -> ExecutableScope
buildInfo :: Executable -> BuildInfo
buildInfo :: BuildInfo
exeScope :: ExecutableScope
modulePath :: FilePath
exeName :: UnqualComponentName
..} =
      [FilePath]
-> BuildInfo -> ([FilePath], ([DynOption], [PackageName]))
extractFromBuildInfo [FilePath
modulePath] BuildInfo
buildInfo
    extractFromTestSuite :: TestSuite -> ([FilePath], ([DynOption], [PackageName]))
extractFromTestSuite TestSuite {[FilePath]
BuildInfo
TestSuiteInterface
UnqualComponentName
testName :: TestSuite -> UnqualComponentName
testInterface :: TestSuite -> TestSuiteInterface
testBuildInfo :: TestSuite -> BuildInfo
testCodeGenerators :: TestSuite -> [FilePath]
testCodeGenerators :: [FilePath]
testBuildInfo :: BuildInfo
testInterface :: TestSuiteInterface
testName :: UnqualComponentName
..} =
      [FilePath]
-> BuildInfo -> ([FilePath], ([DynOption], [PackageName]))
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], [PackageName]))
extractFromBenchmark Benchmark {BuildInfo
BenchmarkInterface
UnqualComponentName
benchmarkName :: Benchmark -> UnqualComponentName
benchmarkInterface :: Benchmark -> BenchmarkInterface
benchmarkBuildInfo :: Benchmark -> BuildInfo
benchmarkBuildInfo :: BuildInfo
benchmarkInterface :: BenchmarkInterface
benchmarkName :: UnqualComponentName
..} =
      [FilePath]
-> BuildInfo -> ([FilePath], ([DynOption], [PackageName]))
extractFromBuildInfo [FilePath]
mainPath BuildInfo
benchmarkBuildInfo
      where
        mainPath :: [FilePath]
mainPath = case BenchmarkInterface
benchmarkInterface of
          BenchmarkExeV10 Version
_ FilePath
p -> [FilePath
p]
          BenchmarkUnsupported {} -> []