module Distribution.Client.SourceFiles (needElaboratedConfiguredPackage) where
import Control.Monad.IO.Class
import Distribution.Client.ProjectPlanning.Types
import Distribution.Client.RebuildMonad
import Distribution.Solver.Types.OptionalStanza
import Distribution.Simple.Glob (matchDirFileGlobWithDie)
import Distribution.Simple.PreProcess
import Distribution.Types.Benchmark
import Distribution.Types.BenchmarkInterface
import Distribution.Types.BuildInfo
import Distribution.Types.Component
import Distribution.Types.ComponentRequestedSpec (ComponentRequestedSpec)
import Distribution.Types.Executable
import Distribution.Types.ForeignLib
import Distribution.Types.Library
import Distribution.Types.PackageDescription
import Distribution.Types.TestSuite
import Distribution.Types.TestSuiteInterface
import Distribution.Utils.Path
import Distribution.ModuleName
import Distribution.Client.Compat.Prelude
import Distribution.Verbosity (normal)
import Prelude ()
import System.FilePath
needElaboratedConfiguredPackage :: ElaboratedConfiguredPackage -> Rebuild ()
needElaboratedConfiguredPackage :: ElaboratedConfiguredPackage -> Rebuild ()
needElaboratedConfiguredPackage ElaboratedConfiguredPackage
elab =
case ElaboratedConfiguredPackage -> ElaboratedPackageOrComponent
elabPkgOrComp ElaboratedConfiguredPackage
elab of
ElabComponent ElaboratedComponent
ecomp -> ElaboratedConfiguredPackage -> ElaboratedComponent -> Rebuild ()
needElaboratedComponent ElaboratedConfiguredPackage
elab ElaboratedComponent
ecomp
ElabPackage ElaboratedPackage
epkg -> ElaboratedConfiguredPackage -> ElaboratedPackage -> Rebuild ()
needElaboratedPackage ElaboratedConfiguredPackage
elab ElaboratedPackage
epkg
needElaboratedPackage :: ElaboratedConfiguredPackage -> ElaboratedPackage -> Rebuild ()
needElaboratedPackage :: ElaboratedConfiguredPackage -> ElaboratedPackage -> Rebuild ()
needElaboratedPackage ElaboratedConfiguredPackage
elab ElaboratedPackage
epkg =
(Component -> Rebuild ()) -> [Component] -> Rebuild ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ (PackageDescription -> Component -> Rebuild ()
needComponent PackageDescription
pkg_descr) (PackageDescription -> ComponentRequestedSpec -> [Component]
enabledComponents PackageDescription
pkg_descr ComponentRequestedSpec
enabled)
where
pkg_descr :: PackageDescription
pkg_descr :: PackageDescription
pkg_descr = ElaboratedConfiguredPackage -> PackageDescription
elabPkgDescription ElaboratedConfiguredPackage
elab
enabled_stanzas :: OptionalStanzaSet
enabled_stanzas :: OptionalStanzaSet
enabled_stanzas = ElaboratedPackage -> OptionalStanzaSet
pkgStanzasEnabled ElaboratedPackage
epkg
enabled :: ComponentRequestedSpec
enabled :: ComponentRequestedSpec
enabled = OptionalStanzaSet -> ComponentRequestedSpec
enableStanzas OptionalStanzaSet
enabled_stanzas
needElaboratedComponent :: ElaboratedConfiguredPackage -> ElaboratedComponent -> Rebuild ()
needElaboratedComponent :: ElaboratedConfiguredPackage -> ElaboratedComponent -> Rebuild ()
needElaboratedComponent ElaboratedConfiguredPackage
elab ElaboratedComponent
ecomp =
case Maybe Component
mb_comp of
Maybe Component
Nothing -> Rebuild ()
needSetup
Just Component
comp -> PackageDescription -> Component -> Rebuild ()
needComponent PackageDescription
pkg_descr Component
comp
where
pkg_descr :: PackageDescription
pkg_descr :: PackageDescription
pkg_descr = ElaboratedConfiguredPackage -> PackageDescription
elabPkgDescription ElaboratedConfiguredPackage
elab
mb_comp :: Maybe Component
mb_comp :: Maybe Component
mb_comp = (ComponentName -> Component)
-> Maybe ComponentName -> Maybe Component
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (PackageDescription -> ComponentName -> Component
getComponent PackageDescription
pkg_descr) (ElaboratedComponent -> Maybe ComponentName
compComponentName ElaboratedComponent
ecomp)
needComponent :: PackageDescription -> Component -> Rebuild ()
needComponent :: PackageDescription -> Component -> Rebuild ()
needComponent PackageDescription
pkg_descr Component
comp =
case Component
comp of
CLib Library
lib -> PackageDescription -> Library -> Rebuild ()
needLibrary PackageDescription
pkg_descr Library
lib
CFLib ForeignLib
flib -> PackageDescription -> ForeignLib -> Rebuild ()
needForeignLib PackageDescription
pkg_descr ForeignLib
flib
CExe Executable
exe -> PackageDescription -> Executable -> Rebuild ()
needExecutable PackageDescription
pkg_descr Executable
exe
CTest TestSuite
test -> PackageDescription -> TestSuite -> Rebuild ()
needTestSuite PackageDescription
pkg_descr TestSuite
test
CBench Benchmark
bench -> PackageDescription -> Benchmark -> Rebuild ()
needBenchmark PackageDescription
pkg_descr Benchmark
bench
needSetup :: Rebuild ()
needSetup :: Rebuild ()
needSetup = (FilePath -> FilePath) -> [FilePath] -> Rebuild (Maybe FilePath)
forall a. (a -> FilePath) -> [a] -> Rebuild (Maybe a)
findFirstFileMonitored FilePath -> FilePath
forall a. a -> a
id [FilePath
"Setup.hs", FilePath
"Setup.lhs"] Rebuild (Maybe FilePath) -> Rebuild () -> Rebuild ()
forall a b. Rebuild a -> Rebuild b -> Rebuild b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> Rebuild ()
forall a. a -> Rebuild a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
needLibrary :: PackageDescription -> Library -> Rebuild ()
needLibrary :: PackageDescription -> Library -> Rebuild ()
needLibrary
PackageDescription
pkg_descr
( Library
{ exposedModules :: Library -> [ModuleName]
exposedModules = [ModuleName]
modules
, signatures :: Library -> [ModuleName]
signatures = [ModuleName]
sigs
, libBuildInfo :: Library -> BuildInfo
libBuildInfo = BuildInfo
bi
}
) =
PackageDescription -> BuildInfo -> [ModuleName] -> Rebuild ()
needBuildInfo PackageDescription
pkg_descr BuildInfo
bi ([ModuleName]
modules [ModuleName] -> [ModuleName] -> [ModuleName]
forall a. [a] -> [a] -> [a]
++ [ModuleName]
sigs)
needForeignLib :: PackageDescription -> ForeignLib -> Rebuild ()
needForeignLib :: PackageDescription -> ForeignLib -> Rebuild ()
needForeignLib
PackageDescription
pkg_descr
( ForeignLib
{ foreignLibModDefFile :: ForeignLib -> [RelativePath Source 'File]
foreignLibModDefFile = [RelativePath Source 'File]
fs
, foreignLibBuildInfo :: ForeignLib -> BuildInfo
foreignLibBuildInfo = BuildInfo
bi
}
) =
do
(RelativePath Source 'File -> Rebuild ())
-> [RelativePath Source 'File] -> Rebuild ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ (FilePath -> Rebuild ()
needIfExists (FilePath -> Rebuild ())
-> (RelativePath Source 'File -> FilePath)
-> RelativePath Source 'File
-> Rebuild ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RelativePath Source 'File -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath) [RelativePath Source 'File]
fs
PackageDescription -> BuildInfo -> [ModuleName] -> Rebuild ()
needBuildInfo PackageDescription
pkg_descr BuildInfo
bi []
needExecutable :: PackageDescription -> Executable -> Rebuild ()
needExecutable :: PackageDescription -> Executable -> Rebuild ()
needExecutable
PackageDescription
pkg_descr
( Executable
{ modulePath :: Executable -> RelativePath Source 'File
modulePath = RelativePath Source 'File
mainPath
, buildInfo :: Executable -> BuildInfo
buildInfo = BuildInfo
bi
}
) =
do
PackageDescription -> BuildInfo -> [ModuleName] -> Rebuild ()
needBuildInfo PackageDescription
pkg_descr BuildInfo
bi []
BuildInfo -> FilePath -> Rebuild ()
needMainFile BuildInfo
bi (FilePath -> Rebuild ()) -> FilePath -> Rebuild ()
forall a b. (a -> b) -> a -> b
$ RelativePath Source 'File -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath RelativePath Source 'File
mainPath
needTestSuite :: PackageDescription -> TestSuite -> Rebuild ()
needTestSuite :: PackageDescription -> TestSuite -> Rebuild ()
needTestSuite PackageDescription
pkg_descr TestSuite
t =
case TestSuite -> TestSuiteInterface
testInterface TestSuite
t of
TestSuiteExeV10 Version
_ RelativePath Source 'File
mainPath -> do
PackageDescription -> BuildInfo -> [ModuleName] -> Rebuild ()
needBuildInfo PackageDescription
pkg_descr BuildInfo
bi []
BuildInfo -> FilePath -> Rebuild ()
needMainFile BuildInfo
bi (FilePath -> Rebuild ()) -> FilePath -> Rebuild ()
forall a b. (a -> b) -> a -> b
$ RelativePath Source 'File -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath RelativePath Source 'File
mainPath
TestSuiteLibV09 Version
_ ModuleName
m ->
PackageDescription -> BuildInfo -> [ModuleName] -> Rebuild ()
needBuildInfo PackageDescription
pkg_descr BuildInfo
bi [ModuleName
m]
TestSuiteUnsupported TestType
_ -> () -> Rebuild ()
forall a. a -> Rebuild a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
where
bi :: BuildInfo
bi :: BuildInfo
bi = TestSuite -> BuildInfo
testBuildInfo TestSuite
t
needMainFile :: BuildInfo -> FilePath -> Rebuild ()
needMainFile :: BuildInfo -> FilePath -> Rebuild ()
needMainFile BuildInfo
bi FilePath
mainPath = do
Maybe FilePath
ppFile <-
[Suffix] -> [FilePath] -> FilePath -> Rebuild (Maybe FilePath)
findFileWithExtensionMonitored
([PPSuffixHandler] -> [Suffix]
ppSuffixes [PPSuffixHandler]
knownSuffixHandlers)
((SymbolicPathX 'AllowAbsolute Pkg ('Dir Source) -> FilePath)
-> [SymbolicPathX 'AllowAbsolute Pkg ('Dir Source)] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map SymbolicPathX 'AllowAbsolute Pkg ('Dir Source) -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath (BuildInfo -> [SymbolicPathX 'AllowAbsolute Pkg ('Dir Source)]
hsSourceDirs BuildInfo
bi))
(FilePath -> FilePath
dropExtension FilePath
mainPath)
case Maybe FilePath
ppFile of
Maybe FilePath
Nothing ->
[FilePath] -> FilePath -> Rebuild (Maybe FilePath)
findFileMonitored ((SymbolicPathX 'AllowAbsolute Pkg ('Dir Source) -> FilePath)
-> [SymbolicPathX 'AllowAbsolute Pkg ('Dir Source)] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map SymbolicPathX 'AllowAbsolute Pkg ('Dir Source) -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath (BuildInfo -> [SymbolicPathX 'AllowAbsolute Pkg ('Dir Source)]
hsSourceDirs BuildInfo
bi)) FilePath
mainPath
Rebuild (Maybe FilePath)
-> (Maybe FilePath -> Rebuild ()) -> Rebuild ()
forall a b. Rebuild a -> (a -> Rebuild b) -> Rebuild b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Rebuild ()
-> (FilePath -> Rebuild ()) -> Maybe FilePath -> Rebuild ()
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (() -> Rebuild ()
forall a. a -> Rebuild a
forall (m :: * -> *) a. Monad m => a -> m a
return ()) FilePath -> Rebuild ()
need
Just FilePath
pp -> FilePath -> Rebuild ()
need FilePath
pp
needBenchmark :: PackageDescription -> Benchmark -> Rebuild ()
needBenchmark :: PackageDescription -> Benchmark -> Rebuild ()
needBenchmark PackageDescription
pkg_descr Benchmark
bm =
case Benchmark -> BenchmarkInterface
benchmarkInterface Benchmark
bm of
BenchmarkExeV10 Version
_ RelativePath Source 'File
mainPath -> do
PackageDescription -> BuildInfo -> [ModuleName] -> Rebuild ()
needBuildInfo PackageDescription
pkg_descr BuildInfo
bi []
BuildInfo -> FilePath -> Rebuild ()
needMainFile BuildInfo
bi (FilePath -> Rebuild ()) -> FilePath -> Rebuild ()
forall a b. (a -> b) -> a -> b
$ RelativePath Source 'File -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath RelativePath Source 'File
mainPath
BenchmarkUnsupported BenchmarkType
_ -> () -> Rebuild ()
forall a. a -> Rebuild a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
where
bi :: BuildInfo
bi :: BuildInfo
bi = Benchmark -> BuildInfo
benchmarkBuildInfo Benchmark
bm
needBuildInfo :: PackageDescription -> BuildInfo -> [ModuleName] -> Rebuild ()
needBuildInfo :: PackageDescription -> BuildInfo -> [ModuleName] -> Rebuild ()
needBuildInfo PackageDescription
pkg_descr BuildInfo
bi [ModuleName]
modules = do
[Suffix] -> Rebuild ()
findNeededModules [Suffix]
builtinHaskellSuffixes
[Suffix] -> Rebuild ()
findNeededModules [Suffix]
builtinHaskellBootSuffixes
FilePath
root <- Rebuild FilePath
askRoot
[SymbolicPathX 'OnlyRelative Pkg 'File]
expandedExtraSrcFiles <- IO [SymbolicPathX 'OnlyRelative Pkg 'File]
-> Rebuild [SymbolicPathX 'OnlyRelative Pkg 'File]
forall a. IO a -> Rebuild a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [SymbolicPathX 'OnlyRelative Pkg 'File]
-> Rebuild [SymbolicPathX 'OnlyRelative Pkg 'File])
-> IO [SymbolicPathX 'OnlyRelative Pkg 'File]
-> Rebuild [SymbolicPathX 'OnlyRelative Pkg 'File]
forall a b. (a -> b) -> a -> b
$
([[SymbolicPathX 'OnlyRelative Pkg 'File]]
-> [SymbolicPathX 'OnlyRelative Pkg 'File])
-> IO [[SymbolicPathX 'OnlyRelative Pkg 'File]]
-> IO [SymbolicPathX 'OnlyRelative Pkg 'File]
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [[SymbolicPathX 'OnlyRelative Pkg 'File]]
-> [SymbolicPathX 'OnlyRelative Pkg 'File]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (IO [[SymbolicPathX 'OnlyRelative Pkg 'File]]
-> IO [SymbolicPathX 'OnlyRelative Pkg 'File])
-> ((SymbolicPathX 'OnlyRelative Pkg 'File
-> IO [SymbolicPathX 'OnlyRelative Pkg 'File])
-> IO [[SymbolicPathX 'OnlyRelative Pkg 'File]])
-> (SymbolicPathX 'OnlyRelative Pkg 'File
-> IO [SymbolicPathX 'OnlyRelative Pkg 'File])
-> IO [SymbolicPathX 'OnlyRelative Pkg 'File]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [SymbolicPathX 'OnlyRelative Pkg 'File]
-> (SymbolicPathX 'OnlyRelative Pkg 'File
-> IO [SymbolicPathX 'OnlyRelative Pkg 'File])
-> IO [[SymbolicPathX 'OnlyRelative Pkg 'File]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for (PackageDescription -> [SymbolicPathX 'OnlyRelative Pkg 'File]
extraSrcFiles PackageDescription
pkg_descr) ((SymbolicPathX 'OnlyRelative Pkg 'File
-> IO [SymbolicPathX 'OnlyRelative Pkg 'File])
-> IO [SymbolicPathX 'OnlyRelative Pkg 'File])
-> (SymbolicPathX 'OnlyRelative Pkg 'File
-> IO [SymbolicPathX 'OnlyRelative Pkg 'File])
-> IO [SymbolicPathX 'OnlyRelative Pkg 'File]
forall a b. (a -> b) -> a -> b
$
\SymbolicPathX 'OnlyRelative Pkg 'File
fpath ->
Verbosity
-> (forall res. Verbosity -> CabalException -> IO [res])
-> CabalSpecVersion
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPathX 'OnlyRelative Pkg 'File
-> IO [SymbolicPathX 'OnlyRelative Pkg 'File]
forall dir (allowAbs :: AllowAbsolute) (file :: FileOrDir).
Verbosity
-> (forall res. Verbosity -> CabalException -> IO [res])
-> CabalSpecVersion
-> Maybe (SymbolicPath CWD ('Dir dir))
-> SymbolicPathX allowAbs dir file
-> IO [SymbolicPathX allowAbs dir file]
matchDirFileGlobWithDie Verbosity
normal (\Verbosity
_ CabalException
_ -> [res] -> IO [res]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return []) (PackageDescription -> CabalSpecVersion
specVersion PackageDescription
pkg_descr) (SymbolicPath CWD ('Dir Pkg) -> Maybe (SymbolicPath CWD ('Dir Pkg))
forall a. a -> Maybe a
Just (SymbolicPath CWD ('Dir Pkg)
-> Maybe (SymbolicPath CWD ('Dir Pkg)))
-> SymbolicPath CWD ('Dir Pkg)
-> Maybe (SymbolicPath CWD ('Dir Pkg))
forall a b. (a -> b) -> a -> b
$ FilePath -> SymbolicPath CWD ('Dir Pkg)
forall from (to :: FileOrDir). FilePath -> SymbolicPath from to
makeSymbolicPath FilePath
root) SymbolicPathX 'OnlyRelative Pkg 'File
fpath
(FilePath -> Rebuild ()) -> [FilePath] -> Rebuild ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ FilePath -> Rebuild ()
needIfExists ([FilePath] -> Rebuild ()) -> [FilePath] -> Rebuild ()
forall a b. (a -> b) -> a -> b
$
[[FilePath]] -> [FilePath]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ (SymbolicPath Pkg 'File -> FilePath)
-> [SymbolicPath Pkg 'File] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map SymbolicPath Pkg 'File -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath ([SymbolicPath Pkg 'File] -> [FilePath])
-> [SymbolicPath Pkg 'File] -> [FilePath]
forall a b. (a -> b) -> a -> b
$ BuildInfo -> [SymbolicPath Pkg 'File]
cSources BuildInfo
bi
, (SymbolicPath Pkg 'File -> FilePath)
-> [SymbolicPath Pkg 'File] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map SymbolicPath Pkg 'File -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath ([SymbolicPath Pkg 'File] -> [FilePath])
-> [SymbolicPath Pkg 'File] -> [FilePath]
forall a b. (a -> b) -> a -> b
$ BuildInfo -> [SymbolicPath Pkg 'File]
cxxSources BuildInfo
bi
, (SymbolicPath Pkg 'File -> FilePath)
-> [SymbolicPath Pkg 'File] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map SymbolicPath Pkg 'File -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath ([SymbolicPath Pkg 'File] -> [FilePath])
-> [SymbolicPath Pkg 'File] -> [FilePath]
forall a b. (a -> b) -> a -> b
$ BuildInfo -> [SymbolicPath Pkg 'File]
jsSources BuildInfo
bi
, (SymbolicPath Pkg 'File -> FilePath)
-> [SymbolicPath Pkg 'File] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map SymbolicPath Pkg 'File -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath ([SymbolicPath Pkg 'File] -> [FilePath])
-> [SymbolicPath Pkg 'File] -> [FilePath]
forall a b. (a -> b) -> a -> b
$ BuildInfo -> [SymbolicPath Pkg 'File]
cmmSources BuildInfo
bi
, (SymbolicPath Pkg 'File -> FilePath)
-> [SymbolicPath Pkg 'File] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map SymbolicPath Pkg 'File -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath ([SymbolicPath Pkg 'File] -> [FilePath])
-> [SymbolicPath Pkg 'File] -> [FilePath]
forall a b. (a -> b) -> a -> b
$ BuildInfo -> [SymbolicPath Pkg 'File]
asmSources BuildInfo
bi
, (SymbolicPathX 'OnlyRelative Pkg 'File -> FilePath)
-> [SymbolicPathX 'OnlyRelative Pkg 'File] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map SymbolicPathX 'OnlyRelative Pkg 'File -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath ([SymbolicPathX 'OnlyRelative Pkg 'File] -> [FilePath])
-> [SymbolicPathX 'OnlyRelative Pkg 'File] -> [FilePath]
forall a b. (a -> b) -> a -> b
$ [SymbolicPathX 'OnlyRelative Pkg 'File]
expandedExtraSrcFiles
]
[FilePath] -> (FilePath -> Rebuild ()) -> Rebuild ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ ((RelativePath Include 'File -> FilePath)
-> [RelativePath Include 'File] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap RelativePath Include 'File -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath ([RelativePath Include 'File] -> [FilePath])
-> [RelativePath Include 'File] -> [FilePath]
forall a b. (a -> b) -> a -> b
$ BuildInfo -> [RelativePath Include 'File]
installIncludes BuildInfo
bi) ((FilePath -> Rebuild ()) -> Rebuild ())
-> (FilePath -> Rebuild ()) -> Rebuild ()
forall a b. (a -> b) -> a -> b
$ \FilePath
f ->
[FilePath] -> FilePath -> Rebuild (Maybe FilePath)
findFileMonitored (FilePath
"." FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: (SymbolicPathX 'AllowAbsolute Pkg ('Dir Include) -> FilePath)
-> [SymbolicPathX 'AllowAbsolute Pkg ('Dir Include)] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SymbolicPathX 'AllowAbsolute Pkg ('Dir Include) -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath (BuildInfo -> [SymbolicPathX 'AllowAbsolute Pkg ('Dir Include)]
includeDirs BuildInfo
bi)) FilePath
f
Rebuild (Maybe FilePath)
-> (Maybe FilePath -> Rebuild ()) -> Rebuild ()
forall a b. Rebuild a -> (a -> Rebuild b) -> Rebuild b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Rebuild ()
-> (FilePath -> Rebuild ()) -> Maybe FilePath -> Rebuild ()
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (() -> Rebuild ()
forall a. a -> Rebuild a
forall (m :: * -> *) a. Monad m => a -> m a
return ()) FilePath -> Rebuild ()
need
where
findNeededModules :: [Suffix] -> Rebuild ()
findNeededModules :: [Suffix] -> Rebuild ()
findNeededModules [Suffix]
exts =
(ModuleName -> Rebuild ()) -> [ModuleName] -> Rebuild ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_
([Suffix] -> ModuleName -> Rebuild ()
findNeededModule [Suffix]
exts)
([ModuleName]
modules [ModuleName] -> [ModuleName] -> [ModuleName]
forall a. [a] -> [a] -> [a]
++ BuildInfo -> [ModuleName]
otherModules BuildInfo
bi)
findNeededModule :: [Suffix] -> ModuleName -> Rebuild ()
findNeededModule :: [Suffix] -> ModuleName -> Rebuild ()
findNeededModule [Suffix]
exts ModuleName
m =
[Suffix] -> [FilePath] -> FilePath -> Rebuild (Maybe FilePath)
findFileWithExtensionMonitored
([PPSuffixHandler] -> [Suffix]
ppSuffixes [PPSuffixHandler]
knownSuffixHandlers [Suffix] -> [Suffix] -> [Suffix]
forall a. [a] -> [a] -> [a]
++ [Suffix]
exts)
((SymbolicPathX 'AllowAbsolute Pkg ('Dir Source) -> FilePath)
-> [SymbolicPathX 'AllowAbsolute Pkg ('Dir Source)] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map SymbolicPathX 'AllowAbsolute Pkg ('Dir Source) -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath (BuildInfo -> [SymbolicPathX 'AllowAbsolute Pkg ('Dir Source)]
hsSourceDirs BuildInfo
bi))
(ModuleName -> FilePath
toFilePath ModuleName
m)
Rebuild (Maybe FilePath)
-> (Maybe FilePath -> Rebuild ()) -> Rebuild ()
forall a b. Rebuild a -> (a -> Rebuild b) -> Rebuild b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Rebuild ()
-> (FilePath -> Rebuild ()) -> Maybe FilePath -> Rebuild ()
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (() -> Rebuild ()
forall a. a -> Rebuild a
forall (m :: * -> *) a. Monad m => a -> m a
return ()) FilePath -> Rebuild ()
need