module Distribution.Simple.AutoExpose where
import Control.Exception(catch,IOException)
import Control.Monad((>=>),filterM)
import Control.Monad.Extra(ifM,notM,whenJust)
import Data.List(intercalate,nub)
import Distribution.Compat.Lens((%~))
import Distribution.ModuleName(ModuleName,fromString,validModuleComponent)
import Distribution.PackageDescription(hsSourceDirs,buildInfo,testBuildInfo,benchmarkBuildInfo,executables,testSuites,benchmarks,libBuildInfo,subLibraries,library,Library,GenericPackageDescription(..),HookedBuildInfo,Executable,TestSuite,Benchmark,condTreeData,packageDescription)
import Distribution.Simple.BuildPaths(autogenPathsModuleName)
import Distribution.Simple.PreProcess(knownSuffixHandlers)
import Distribution.Simple.Setup(BuildFlags, ReplFlags, HscolourFlags, HaddockFlags, CopyFlags, InstallFlags, TestFlags, BenchmarkFlags, RegisterFlags, DoctestFlags, ConfigFlags,fromFlag, configVerbosity)
import Distribution.Simple.UserHooks(UserHooks,Args,hookedPreProcessors, buildHook,replHook,hscolourHook,doctestHook,haddockHook,copyHook,instHook,testHook,benchHook,regHook,unregHook,confHook)
import Distribution.Simple.Utils(findPackageDesc,notice)
import Distribution.Types.LocalBuildInfo(LocalBuildInfo)
import Distribution.Types.PackageDescription(PackageDescription,package)
import GHC.Stack(HasCallStack)
import System.Directory(makeAbsolute,listDirectory,doesDirectoryExist,withCurrentDirectory,pathIsSymbolicLink,getTemporaryDirectory)
import System.FilePath(splitDirectories, dropExtension, takeExtension,equalFilePath,makeRelative,(</>),(<.>))
import qualified Distribution.Simple(defaultMainWithHooks,simpleUserHooks)
import qualified Distribution.Types.BuildInfo.Lens as L
import qualified Distribution.Types.Library.Lens as L
import Distribution.Pretty(prettyShow)
import Distribution.Types.PackageId(PackageIdentifier(pkgName,pkgVersion))
import Distribution.Types.Version()
import Distribution.PackageDescription.PrettyPrint(writeGenericPackageDescription)
defaultMain :: IO ()
defaultMain :: IO ()
defaultMain = UserHooks -> IO ()
defaultMainWithHooks UserHooks
Distribution.Simple.simpleUserHooks
defaultMainWithHooks :: UserHooks -> IO ()
defaultMainWithHooks :: UserHooks -> IO ()
defaultMainWithHooks UserHooks
uhs = UserHooks -> IO ()
Distribution.Simple.defaultMainWithHooks (Maybe WriteGeneratedCabal -> UserHooks -> UserHooks
autoExposeHooks Maybe WriteGeneratedCabal
forall a. Maybe a
Nothing UserHooks
uhs)
defaultMainGenerateCabal :: IO ()
defaultMainGenerateCabal :: IO ()
defaultMainGenerateCabal = do
WriteGeneratedCabal
defaultCabalWriter <- IO WriteGeneratedCabal
defaultWriteGeneratedCabal
WriteGeneratedCabal -> UserHooks -> IO ()
defaultMainWithHooksGenerateCabal WriteGeneratedCabal
defaultCabalWriter UserHooks
Distribution.Simple.simpleUserHooks
defaultMainWithHooksGenerateCabal :: WriteGeneratedCabal -> UserHooks -> IO ()
defaultMainWithHooksGenerateCabal :: WriteGeneratedCabal -> UserHooks -> IO ()
defaultMainWithHooksGenerateCabal WriteGeneratedCabal
writeGeneratedCabal UserHooks
uhs =
UserHooks -> IO ()
Distribution.Simple.defaultMainWithHooks (Maybe WriteGeneratedCabal -> UserHooks -> UserHooks
autoExposeHooks (WriteGeneratedCabal -> Maybe WriteGeneratedCabal
forall a. a -> Maybe a
Just WriteGeneratedCabal
writeGeneratedCabal) UserHooks
uhs)
data WriteGeneratedCabal =
WriteGeneratedCabal
{ WriteGeneratedCabal -> FilePath
writeGeneratedCabalPath :: FilePath
, WriteGeneratedCabal -> GenericPackageDescription -> FilePath
writeGeneratedCabalName :: GenericPackageDescription -> FilePath
}
defaultWriteGeneratedCabal :: IO WriteGeneratedCabal
defaultWriteGeneratedCabal :: IO WriteGeneratedCabal
defaultWriteGeneratedCabal = do
FilePath
tmp <- IO FilePath
getTemporaryDirectory
WriteGeneratedCabal -> IO WriteGeneratedCabal
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FilePath
-> (GenericPackageDescription -> FilePath) -> WriteGeneratedCabal
WriteGeneratedCabal FilePath
tmp GenericPackageDescription -> FilePath
defaultGeneratedCabalName)
moduleNamesToExpose
:: [String]
-> [FilePath]
-> [ModuleName]
moduleNamesToExpose :: [FilePath] -> [FilePath] -> [ModuleName]
moduleNamesToExpose [FilePath]
extensions =
([FilePath] -> ModuleName) -> [[FilePath]] -> [ModuleName]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> ModuleName
forall a. IsString a => FilePath -> a
fromString (FilePath -> ModuleName)
-> ([FilePath] -> FilePath) -> [FilePath] -> ModuleName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> [FilePath] -> FilePath
forall a. [a] -> [[a]] -> [a]
intercalate FilePath
".")
([[FilePath]] -> [ModuleName])
-> ([FilePath] -> [[FilePath]]) -> [FilePath] -> [ModuleName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([FilePath] -> Bool) -> [[FilePath]] -> [[FilePath]]
forall a. (a -> Bool) -> [a] -> [a]
filter ((FilePath -> Bool) -> [FilePath] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all FilePath -> Bool
validModuleComponent)
([[FilePath]] -> [[FilePath]])
-> ([FilePath] -> [[FilePath]]) -> [FilePath] -> [[FilePath]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath -> [FilePath]) -> [FilePath] -> [[FilePath]]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> [FilePath]
toModuleComponents
([FilePath] -> [[FilePath]])
-> ([FilePath] -> [FilePath]) -> [FilePath] -> [[FilePath]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath -> Bool) -> [FilePath] -> [FilePath]
forall a. (a -> Bool) -> [a] -> [a]
filter FilePath -> Bool
hasExtension
where
hasExtension :: FilePath -> Bool
hasExtension :: FilePath -> Bool
hasExtension FilePath
f =
FilePath -> [FilePath] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem
(Int -> FilePath -> FilePath
forall a. Int -> [a] -> [a]
drop Int
1 (FilePath -> FilePath
takeExtension FilePath
f))
[FilePath]
extensions
toModuleComponents :: FilePath -> [String]
toModuleComponents :: FilePath -> [FilePath]
toModuleComponents =
FilePath -> [FilePath]
splitDirectories (FilePath -> [FilePath])
-> (FilePath -> FilePath) -> FilePath -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
dropExtension
getDirectoryContents
:: HasCallStack
=> FilePath
-> [FilePath]
-> IO [FilePath]
getDirectoryContents :: FilePath -> [FilePath] -> IO [FilePath]
getDirectoryContents FilePath
dir [FilePath]
excludedDirs = do
((FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> FilePath -> FilePath
makeRelative FilePath
dir)) ([FilePath] -> [FilePath]) -> IO [FilePath] -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [FilePath] -> [FilePath] -> IO [FilePath]
go [FilePath
dir] []
where
go :: [FilePath] -> [FilePath] -> IO [FilePath]
go :: [FilePath] -> [FilePath] -> IO [FilePath]
go (FilePath
f:[FilePath]
fs) [FilePath]
accum
| (FilePath -> Bool) -> [FilePath] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (FilePath -> FilePath -> Bool
equalFilePath FilePath
f) [FilePath]
excludedDirs = [FilePath] -> [FilePath] -> IO [FilePath]
go [FilePath]
fs [FilePath]
accum
| Bool
otherwise =
IO Bool -> IO [FilePath] -> IO [FilePath] -> IO [FilePath]
forall (m :: * -> *) a. Monad m => m Bool -> m a -> m a -> m a
ifM (FilePath -> IO Bool
doesDirectoryExist FilePath
f)
(IO [FilePath] -> (IOException -> IO [FilePath]) -> IO [FilePath]
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
catch
(FilePath -> IO [FilePath] -> IO [FilePath]
forall a. FilePath -> IO a -> IO a
withCurrentDirectory FilePath
f (IO [FilePath] -> IO [FilePath]) -> IO [FilePath] -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ do
[FilePath]
contents <-
(FilePath -> IO [FilePath]
listDirectory (FilePath -> IO [FilePath])
-> ([FilePath] -> IO [FilePath]) -> FilePath -> IO [FilePath]
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (FilePath -> IO Bool) -> [FilePath] -> IO [FilePath]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM (IO Bool -> IO Bool
forall (m :: * -> *). Functor m => m Bool -> m Bool
notM (IO Bool -> IO Bool)
-> (FilePath -> IO Bool) -> FilePath -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO Bool
pathIsSymbolicLink) ([FilePath] -> IO [FilePath])
-> ([FilePath] -> IO [FilePath]) -> [FilePath] -> IO [FilePath]
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (FilePath -> IO FilePath) -> [FilePath] -> IO [FilePath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM FilePath -> IO FilePath
makeAbsolute) FilePath
f
[FilePath] -> [FilePath] -> IO [FilePath]
go ([FilePath]
contents [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath]
fs) [FilePath]
accum)
(\(IOException
_ :: IOException) -> [FilePath] -> [FilePath] -> IO [FilePath]
go [FilePath]
fs [FilePath]
accum))
([FilePath] -> [FilePath] -> IO [FilePath]
go [FilePath]
fs (FilePath
fFilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
:[FilePath]
accum))
go [] [FilePath]
accum = [FilePath] -> IO [FilePath]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [FilePath]
accum
data ExposedLib =
ExposedLib
{ ExposedLib -> [ModuleName]
exposedLibModules :: [ModuleName]
, ExposedLib -> [ModuleName]
exposedLibSignatures :: [ModuleName]
}
deriving Int -> ExposedLib -> FilePath -> FilePath
[ExposedLib] -> FilePath -> FilePath
ExposedLib -> FilePath
(Int -> ExposedLib -> FilePath -> FilePath)
-> (ExposedLib -> FilePath)
-> ([ExposedLib] -> FilePath -> FilePath)
-> Show ExposedLib
forall a.
(Int -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
showList :: [ExposedLib] -> FilePath -> FilePath
$cshowList :: [ExposedLib] -> FilePath -> FilePath
show :: ExposedLib -> FilePath
$cshow :: ExposedLib -> FilePath
showsPrec :: Int -> ExposedLib -> FilePath -> FilePath
$cshowsPrec :: Int -> ExposedLib -> FilePath -> FilePath
Show
data PackageDescriptionSubset =
PackageDescriptionSubset
{ PackageDescriptionSubset -> Maybe Library
packageDescriptionSubsetLibrary :: Maybe Library
, PackageDescriptionSubset -> [Library]
packageDescriptionSubsetSubLibraries :: [Library]
, PackageDescriptionSubset -> [Executable]
packageDescriptionSubsetExecutables :: [Executable]
, PackageDescriptionSubset -> [TestSuite]
packageDescriptionSubsetTestSuites :: [TestSuite]
, PackageDescriptionSubset -> [Benchmark]
packageDescriptionSubsetBenchmarks :: [Benchmark]
}
deriving Int -> PackageDescriptionSubset -> FilePath -> FilePath
[PackageDescriptionSubset] -> FilePath -> FilePath
PackageDescriptionSubset -> FilePath
(Int -> PackageDescriptionSubset -> FilePath -> FilePath)
-> (PackageDescriptionSubset -> FilePath)
-> ([PackageDescriptionSubset] -> FilePath -> FilePath)
-> Show PackageDescriptionSubset
forall a.
(Int -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
showList :: [PackageDescriptionSubset] -> FilePath -> FilePath
$cshowList :: [PackageDescriptionSubset] -> FilePath -> FilePath
show :: PackageDescriptionSubset -> FilePath
$cshow :: PackageDescriptionSubset -> FilePath
showsPrec :: Int -> PackageDescriptionSubset -> FilePath -> FilePath
$cshowsPrec :: Int -> PackageDescriptionSubset -> FilePath -> FilePath
Show
genericPackageDescriptionToSubset :: GenericPackageDescription -> PackageDescriptionSubset
genericPackageDescriptionToSubset :: GenericPackageDescription -> PackageDescriptionSubset
genericPackageDescriptionToSubset GenericPackageDescription
gpd =
Maybe Library
-> [Library]
-> [Executable]
-> [TestSuite]
-> [Benchmark]
-> PackageDescriptionSubset
PackageDescriptionSubset
((CondTree ConfVar [Dependency] Library -> Library)
-> Maybe (CondTree ConfVar [Dependency] Library) -> Maybe Library
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CondTree ConfVar [Dependency] Library -> Library
forall v c a. CondTree v c a -> a
condTreeData (GenericPackageDescription
-> Maybe (CondTree ConfVar [Dependency] Library)
condLibrary GenericPackageDescription
gpd))
(((UnqualComponentName, CondTree ConfVar [Dependency] Library)
-> Library)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> [Library]
forall a b. (a -> b) -> [a] -> [b]
map (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) (GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
condSubLibraries GenericPackageDescription
gpd))
(((UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> Executable)
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> [Executable]
forall a b. (a -> b) -> [a] -> [b]
map (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) (GenericPackageDescription
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
condExecutables GenericPackageDescription
gpd))
(((UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> TestSuite)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [TestSuite]
forall a b. (a -> b) -> [a] -> [b]
map (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) (GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
condTestSuites GenericPackageDescription
gpd))
(((UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> Benchmark)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> [Benchmark]
forall a b. (a -> b) -> [a] -> [b]
map (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) (GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
condBenchmarks GenericPackageDescription
gpd))
packageDescriptionToSubset :: PackageDescription -> PackageDescriptionSubset
packageDescriptionToSubset :: PackageDescription -> PackageDescriptionSubset
packageDescriptionToSubset PackageDescription
pd =
Maybe Library
-> [Library]
-> [Executable]
-> [TestSuite]
-> [Benchmark]
-> PackageDescriptionSubset
PackageDescriptionSubset
(PackageDescription -> Maybe Library
library PackageDescription
pd)
(PackageDescription -> [Library]
subLibraries PackageDescription
pd)
(PackageDescription -> [Executable]
executables PackageDescription
pd)
(PackageDescription -> [TestSuite]
testSuites PackageDescription
pd)
(PackageDescription -> [Benchmark]
benchmarks PackageDescription
pd)
nonLibraryHsSourcePaths :: PackageDescriptionSubset -> [[FilePath]]
nonLibraryHsSourcePaths :: PackageDescriptionSubset -> [[FilePath]]
nonLibraryHsSourcePaths PackageDescriptionSubset
pds =
(BuildInfo -> [FilePath]) -> [BuildInfo] -> [[FilePath]]
forall a b. (a -> b) -> [a] -> [b]
map BuildInfo -> [FilePath]
hsSourceDirs ([BuildInfo] -> [[FilePath]]) -> [BuildInfo] -> [[FilePath]]
forall a b. (a -> b) -> a -> b
$
((Executable -> BuildInfo) -> [Executable] -> [BuildInfo]
forall a b. (a -> b) -> [a] -> [b]
map Executable -> BuildInfo
buildInfo (PackageDescriptionSubset -> [Executable]
packageDescriptionSubsetExecutables PackageDescriptionSubset
pds))
[BuildInfo] -> [BuildInfo] -> [BuildInfo]
forall a. [a] -> [a] -> [a]
++ ((TestSuite -> BuildInfo) -> [TestSuite] -> [BuildInfo]
forall a b. (a -> b) -> [a] -> [b]
map TestSuite -> BuildInfo
testBuildInfo (PackageDescriptionSubset -> [TestSuite]
packageDescriptionSubsetTestSuites PackageDescriptionSubset
pds))
[BuildInfo] -> [BuildInfo] -> [BuildInfo]
forall a. [a] -> [a] -> [a]
++ ((Benchmark -> BuildInfo) -> [Benchmark] -> [BuildInfo]
forall a b. (a -> b) -> [a] -> [b]
map Benchmark -> BuildInfo
benchmarkBuildInfo (PackageDescriptionSubset -> [Benchmark]
packageDescriptionSubsetBenchmarks PackageDescriptionSubset
pds))
indexWithNeighbors :: [a] -> [(a,[a])]
indexWithNeighbors :: [a] -> [(a, [a])]
indexWithNeighbors (a
a:[a]
as) = [(a, [a])] -> [(a, [a])]
forall a. [a] -> [a]
reverse ([a] -> a -> [a] -> [(a, [a])] -> [(a, [a])]
forall a. [a] -> a -> [a] -> [(a, [a])] -> [(a, [a])]
go [] a
a [a]
as [])
where
go :: [a] -> a -> [a] -> [(a, [a])] -> [(a, [a])]
go [] a
x (a
r:[a]
rs) [(a, [a])]
accum = [a] -> a -> [a] -> [(a, [a])] -> [(a, [a])]
go [a
x] a
r [a]
rs ((a
x,(a
ra -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
rs))(a, [a]) -> [(a, [a])] -> [(a, [a])]
forall a. a -> [a] -> [a]
:[(a, [a])]
accum)
go [a]
ls a
x (a
r:[a]
rs) [(a, [a])]
accum = [a] -> a -> [a] -> [(a, [a])] -> [(a, [a])]
go ([a]
ls[a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++[a
x]) a
r [a]
rs ((a
x,([a]
ls[a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++(a
ra -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
rs)))(a, [a]) -> [(a, [a])] -> [(a, [a])]
forall a. a -> [a] -> [a]
:[(a, [a])]
accum)
go [a]
ls a
x [] [(a, [a])]
accum = (a
x,[a]
ls)(a, [a]) -> [(a, [a])] -> [(a, [a])]
forall a. a -> [a] -> [a]
:[(a, [a])]
accum
indexWithNeighbors [] = []
getExposedModules
:: HasCallStack
=> [String]
-> [FilePath]
-> [[FilePath]]
-> IO [ModuleName]
getExposedModules :: [FilePath] -> [FilePath] -> [[FilePath]] -> IO [ModuleName]
getExposedModules [FilePath]
exts [FilePath]
hsSrcDirs [[FilePath]]
otherHsSrcDirs = do
[FilePath]
absHsSrcDirs <- (FilePath -> IO FilePath) -> [FilePath] -> IO [FilePath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM FilePath -> IO FilePath
makeAbsolute [FilePath]
hsSrcDirs
[FilePath]
absOtherHsSrcDirs <- (FilePath -> IO FilePath) -> [FilePath] -> IO [FilePath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM FilePath -> IO FilePath
makeAbsolute ([[FilePath]] -> [FilePath]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[FilePath]]
otherHsSrcDirs)
[FilePath]
contents <-
[[FilePath]] -> [FilePath]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
([[FilePath]] -> [FilePath]) -> IO [[FilePath]] -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ( ((FilePath, [FilePath]) -> IO [FilePath])
-> [(FilePath, [FilePath])] -> IO [[FilePath]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (\(FilePath
srcDir,[FilePath]
excludeDirs) -> HasCallStack => FilePath -> [FilePath] -> IO [FilePath]
FilePath -> [FilePath] -> IO [FilePath]
getDirectoryContents FilePath
srcDir [FilePath]
excludeDirs)
([(FilePath, [FilePath])] -> IO [[FilePath]])
-> [(FilePath, [FilePath])] -> IO [[FilePath]]
forall a b. (a -> b) -> a -> b
$ ((FilePath, [FilePath]) -> (FilePath, [FilePath]))
-> [(FilePath, [FilePath])] -> [(FilePath, [FilePath])]
forall a b. (a -> b) -> [a] -> [b]
map (\(FilePath
srcDir,[FilePath]
otherSrcDirs) -> (FilePath
srcDir,[FilePath]
otherSrcDirs [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath]
absOtherHsSrcDirs))
([(FilePath, [FilePath])] -> [(FilePath, [FilePath])])
-> [(FilePath, [FilePath])] -> [(FilePath, [FilePath])]
forall a b. (a -> b) -> a -> b
$ [FilePath] -> [(FilePath, [FilePath])]
forall a. [a] -> [(a, [a])]
indexWithNeighbors [FilePath]
absHsSrcDirs
)
[ModuleName] -> IO [ModuleName]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([ModuleName] -> IO [ModuleName])
-> [ModuleName] -> IO [ModuleName]
forall a b. (a -> b) -> a -> b
$ [FilePath] -> [FilePath] -> [ModuleName]
moduleNamesToExpose [FilePath]
exts [FilePath]
contents
getExposedLib
:: HasCallStack
=> PackageDescriptionSubset
-> UserHooks
-> IO ExposedLib
getExposedLib :: PackageDescriptionSubset -> UserHooks -> IO ExposedLib
getExposedLib PackageDescriptionSubset
pds UserHooks
uhs =
let excluded :: [[FilePath]]
excluded =
(Library -> [FilePath]) -> [Library] -> [[FilePath]]
forall a b. (a -> b) -> [a] -> [b]
map Library -> [FilePath]
libSrcDir (PackageDescriptionSubset -> [Library]
packageDescriptionSubsetSubLibraries PackageDescriptionSubset
pds) [[FilePath]] -> [[FilePath]] -> [[FilePath]]
forall a. [a] -> [a] -> [a]
++ (PackageDescriptionSubset -> [[FilePath]]
nonLibraryHsSourcePaths PackageDescriptionSubset
pds)
libExposedModules :: Library -> IO [ModuleName]
libExposedModules Library
l =
HasCallStack =>
[FilePath] -> [FilePath] -> [[FilePath]] -> IO [ModuleName]
[FilePath] -> [FilePath] -> [[FilePath]] -> IO [ModuleName]
getExposedModules ([FilePath]
sourceExtensions [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath]
ppExts) (Library -> [FilePath]
libSrcDir Library
l) [[FilePath]]
excluded
libExposedSignatures :: Library -> IO [ModuleName]
libExposedSignatures Library
l =
HasCallStack =>
[FilePath] -> [FilePath] -> [[FilePath]] -> IO [ModuleName]
[FilePath] -> [FilePath] -> [[FilePath]] -> IO [ModuleName]
getExposedModules [FilePath]
hsigExtensions (Library -> [FilePath]
libSrcDir Library
l) [[FilePath]]
excluded
in case (PackageDescriptionSubset -> Maybe Library
packageDescriptionSubsetLibrary PackageDescriptionSubset
pds) of
Maybe Library
Nothing -> ExposedLib -> IO ExposedLib
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([ModuleName] -> [ModuleName] -> ExposedLib
ExposedLib [] [])
Just Library
l -> ([ModuleName] -> [ModuleName] -> ExposedLib)
-> IO ([ModuleName] -> [ModuleName] -> ExposedLib)
forall (f :: * -> *) a. Applicative f => a -> f a
pure [ModuleName] -> [ModuleName] -> ExposedLib
ExposedLib IO ([ModuleName] -> [ModuleName] -> ExposedLib)
-> IO [ModuleName] -> IO ([ModuleName] -> ExposedLib)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Library -> IO [ModuleName]
libExposedModules Library
l) IO ([ModuleName] -> ExposedLib) -> IO [ModuleName] -> IO ExposedLib
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Library -> IO [ModuleName]
libExposedSignatures Library
l)
where
ppExts :: [String]
ppExts :: [FilePath]
ppExts = ([FilePath] -> [FilePath]
forall a. Eq a => [a] -> [a]
nub ([FilePath] -> [FilePath])
-> ([(FilePath,
BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor)]
-> [FilePath])
-> [(FilePath,
BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor)]
-> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((FilePath,
BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor)
-> FilePath)
-> [(FilePath,
BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor)]
-> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath,
BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor)
-> FilePath
forall a b. (a, b) -> a
fst) ((UserHooks
-> [(FilePath,
BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor)]
hookedPreProcessors UserHooks
uhs) [(FilePath,
BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor)]
-> [(FilePath,
BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor)]
-> [(FilePath,
BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor)]
forall a. [a] -> [a] -> [a]
++ [(FilePath,
BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor)]
knownSuffixHandlers)
libSrcDir :: Library -> [FilePath]
libSrcDir :: Library -> [FilePath]
libSrcDir = [FilePath] -> [FilePath]
forall a. Eq a => [a] -> [a]
nub ([FilePath] -> [FilePath])
-> (Library -> [FilePath]) -> Library -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuildInfo -> [FilePath]
hsSourceDirs (BuildInfo -> [FilePath])
-> (Library -> BuildInfo) -> Library -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Library -> BuildInfo
libBuildInfo
withCabalFileDirectory
:: HasCallStack
=> IO a
-> IO a
withCabalFileDirectory :: IO a -> IO a
withCabalFileDirectory IO a
action = do
Either FilePath FilePath
cabalFilePath <- FilePath -> NoCallStackIO (Either FilePath FilePath)
findPackageDesc FilePath
"."
case Either FilePath FilePath
cabalFilePath of
Left FilePath
err -> FilePath -> IO a
forall a. HasCallStack => FilePath -> a
error FilePath
err
Right FilePath
_ -> FilePath -> IO a -> IO a
forall a. FilePath -> IO a -> IO a
withCurrentDirectory FilePath
"." IO a
action
updateLibrary :: ExposedLib -> Library -> Library
updateLibrary :: ExposedLib -> Library -> Library
updateLibrary ExposedLib
exposedLib =
(LensLike Identity Library Library [ModuleName] [ModuleName]
Lens' Library [ModuleName]
L.exposedModules LensLike Identity Library Library [ModuleName] [ModuleName]
-> ([ModuleName] -> [ModuleName]) -> Library -> Library
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ ([ModuleName] -> [ModuleName]
forall a. Eq a => [a] -> [a]
nub ([ModuleName] -> [ModuleName])
-> ([ModuleName] -> [ModuleName]) -> [ModuleName] -> [ModuleName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ModuleName] -> [ModuleName] -> [ModuleName]
forall a. [a] -> [a] -> [a]
(++) (ExposedLib -> [ModuleName]
exposedLibModules ExposedLib
exposedLib)))
(Library -> Library) -> (Library -> Library) -> Library -> Library
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LensLike Identity Library Library [ModuleName] [ModuleName]
Lens' Library [ModuleName]
L.signatures LensLike Identity Library Library [ModuleName] [ModuleName]
-> ([ModuleName] -> [ModuleName]) -> Library -> Library
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ ([ModuleName] -> [ModuleName]
forall a. Eq a => [a] -> [a]
nub ([ModuleName] -> [ModuleName])
-> ([ModuleName] -> [ModuleName]) -> [ModuleName] -> [ModuleName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ModuleName] -> [ModuleName] -> [ModuleName]
forall a. [a] -> [a] -> [a]
(++) (ExposedLib -> [ModuleName]
exposedLibSignatures ExposedLib
exposedLib)))
updatePackageDescription :: HasCallStack => PackageDescription -> UserHooks -> IO PackageDescription
updatePackageDescription :: PackageDescription -> UserHooks -> IO PackageDescription
updatePackageDescription PackageDescription
pd UserHooks
uhs =
IO PackageDescription -> IO PackageDescription
forall a. HasCallStack => IO a -> IO a
withCabalFileDirectory (IO PackageDescription -> IO PackageDescription)
-> IO PackageDescription -> IO PackageDescription
forall a b. (a -> b) -> a -> b
$ do
ExposedLib
exposedLib <- HasCallStack =>
PackageDescriptionSubset -> UserHooks -> IO ExposedLib
PackageDescriptionSubset -> UserHooks -> IO ExposedLib
getExposedLib (PackageDescription -> PackageDescriptionSubset
packageDescriptionToSubset PackageDescription
pd) UserHooks
uhs
let newMainLibrary :: Library -> Library
newMainLibrary =
(LensLike Identity Library Library BuildInfo BuildInfo
Lens' Library BuildInfo
L.libBuildInfo LensLike Identity Library Library BuildInfo BuildInfo
-> (([ModuleName] -> Identity [ModuleName])
-> BuildInfo -> Identity BuildInfo)
-> LensLike Identity Library Library [ModuleName] [ModuleName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([ModuleName] -> Identity [ModuleName])
-> BuildInfo -> Identity BuildInfo
forall a. HasBuildInfo a => Lens' a [ModuleName]
L.otherModules LensLike Identity Library Library [ModuleName] [ModuleName]
-> ([ModuleName] -> [ModuleName]) -> Library -> Library
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ ([ModuleName] -> [ModuleName]
forall a. Eq a => [a] -> [a]
nub ([ModuleName] -> [ModuleName])
-> ([ModuleName] -> [ModuleName]) -> [ModuleName] -> [ModuleName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ModuleName] -> [ModuleName] -> [ModuleName]
forall a. [a] -> [a] -> [a]
(++) [(PackageDescription -> ModuleName
autogenPathsModuleName PackageDescription
pd)]))
(Library -> Library) -> (Library -> Library) -> Library -> Library
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExposedLib -> Library -> Library
updateLibrary ExposedLib
exposedLib
PackageDescription -> IO PackageDescription
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PackageDescription
pd { library :: Maybe Library
library = (Library -> Library) -> Maybe Library -> Maybe Library
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Library -> Library
newMainLibrary (PackageDescription -> Maybe Library
library PackageDescription
pd) })
updateGenericPackageDescription :: HasCallStack => GenericPackageDescription -> UserHooks -> IO GenericPackageDescription
updateGenericPackageDescription :: GenericPackageDescription
-> UserHooks -> IO GenericPackageDescription
updateGenericPackageDescription GenericPackageDescription
gpd UserHooks
uhs =
let updateCondTreeLib :: ExposedLib -> CondTree v c Library -> CondTree v c Library
updateCondTreeLib ExposedLib
exposedLib CondTree v c Library
condLib =
CondTree v c Library
condLib { condTreeData :: Library
condTreeData = ExposedLib -> Library -> Library
updateLibrary ExposedLib
exposedLib (CondTree v c Library -> Library
forall v c a. CondTree v c a -> a
condTreeData CondTree v c Library
condLib) }
in IO GenericPackageDescription -> IO GenericPackageDescription
forall a. HasCallStack => IO a -> IO a
withCabalFileDirectory (IO GenericPackageDescription -> IO GenericPackageDescription)
-> IO GenericPackageDescription -> IO GenericPackageDescription
forall a b. (a -> b) -> a -> b
$ do
ExposedLib
exposedLib <- HasCallStack =>
PackageDescriptionSubset -> UserHooks -> IO ExposedLib
PackageDescriptionSubset -> UserHooks -> IO ExposedLib
getExposedLib (GenericPackageDescription -> PackageDescriptionSubset
genericPackageDescriptionToSubset GenericPackageDescription
gpd) UserHooks
uhs
GenericPackageDescription -> IO GenericPackageDescription
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GenericPackageDescription -> IO GenericPackageDescription)
-> GenericPackageDescription -> IO GenericPackageDescription
forall a b. (a -> b) -> a -> b
$
GenericPackageDescription
gpd { condLibrary :: Maybe (CondTree ConfVar [Dependency] Library)
condLibrary = (CondTree ConfVar [Dependency] Library
-> CondTree ConfVar [Dependency] Library)
-> Maybe (CondTree ConfVar [Dependency] Library)
-> Maybe (CondTree ConfVar [Dependency] Library)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ExposedLib
-> CondTree ConfVar [Dependency] Library
-> CondTree ConfVar [Dependency] Library
forall v c.
ExposedLib -> CondTree v c Library -> CondTree v c Library
updateCondTreeLib ExposedLib
exposedLib) (GenericPackageDescription
-> Maybe (CondTree ConfVar [Dependency] Library)
condLibrary GenericPackageDescription
gpd) }
defaultGeneratedCabalName :: GenericPackageDescription -> FilePath
defaultGeneratedCabalName :: GenericPackageDescription -> FilePath
defaultGeneratedCabalName GenericPackageDescription
gpd =
let gpdPkg :: GenericPackageDescription -> PackageIdentifier
gpdPkg = PackageDescription -> PackageIdentifier
package (PackageDescription -> PackageIdentifier)
-> (GenericPackageDescription -> PackageDescription)
-> GenericPackageDescription
-> PackageIdentifier
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenericPackageDescription -> PackageDescription
packageDescription
in (PackageName -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow (PackageIdentifier -> PackageName
pkgName (GenericPackageDescription -> PackageIdentifier
gpdPkg GenericPackageDescription
gpd)))
FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"-"
FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ (Version -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow (PackageIdentifier -> Version
pkgVersion (GenericPackageDescription -> PackageIdentifier
gpdPkg GenericPackageDescription
gpd)))
FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"-generated"
FilePath -> FilePath -> FilePath
<.> FilePath
"cabal"
autoExposeConfHook
:: UserHooks
-> Maybe WriteGeneratedCabal
-> (GenericPackageDescription, HookedBuildInfo)
-> ConfigFlags
-> IO LocalBuildInfo
autoExposeConfHook :: UserHooks
-> Maybe WriteGeneratedCabal
-> (GenericPackageDescription, HookedBuildInfo)
-> ConfigFlags
-> IO LocalBuildInfo
autoExposeConfHook UserHooks
userHooks Maybe WriteGeneratedCabal
writeGeneratedCabalM (GenericPackageDescription
gpd,HookedBuildInfo
hbi) ConfigFlags
cfs = do
GenericPackageDescription
newGpd <- HasCallStack =>
GenericPackageDescription
-> UserHooks -> IO GenericPackageDescription
GenericPackageDescription
-> UserHooks -> IO GenericPackageDescription
updateGenericPackageDescription GenericPackageDescription
gpd UserHooks
userHooks
Maybe WriteGeneratedCabal
-> (WriteGeneratedCabal -> IO ()) -> IO ()
forall (m :: * -> *) a.
Applicative m =>
Maybe a -> (a -> m ()) -> m ()
whenJust Maybe WriteGeneratedCabal
writeGeneratedCabalM
(\(WriteGeneratedCabal FilePath
outputDir GenericPackageDescription -> FilePath
generatedCabalName) -> do
let f :: FilePath
f = FilePath
outputDir FilePath -> FilePath -> FilePath
</> (GenericPackageDescription -> FilePath
generatedCabalName GenericPackageDescription
newGpd)
Verbosity -> FilePath -> IO ()
notice (Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (ConfigFlags -> Flag Verbosity
configVerbosity ConfigFlags
cfs)) (FilePath
"Writing generated Cabal file: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
f)
FilePath -> GenericPackageDescription -> IO ()
writeGenericPackageDescription FilePath
f GenericPackageDescription
newGpd
)
(UserHooks
-> (GenericPackageDescription, HookedBuildInfo)
-> ConfigFlags
-> IO LocalBuildInfo
confHook UserHooks
userHooks) (GenericPackageDescription
newGpd,HookedBuildInfo
hbi) ConfigFlags
cfs
autoExposeHooks :: Maybe WriteGeneratedCabal -> UserHooks -> UserHooks
autoExposeHooks :: Maybe WriteGeneratedCabal -> UserHooks -> UserHooks
autoExposeHooks Maybe WriteGeneratedCabal
writeGeneratedCabalM UserHooks
userHooks =
UserHooks
userHooks
{ confHook :: (GenericPackageDescription, HookedBuildInfo)
-> ConfigFlags -> IO LocalBuildInfo
confHook = UserHooks
-> Maybe WriteGeneratedCabal
-> (GenericPackageDescription, HookedBuildInfo)
-> ConfigFlags
-> IO LocalBuildInfo
autoExposeConfHook UserHooks
userHooks Maybe WriteGeneratedCabal
writeGeneratedCabalM
, buildHook :: PackageDescription
-> LocalBuildInfo -> UserHooks -> BuildFlags -> IO ()
buildHook = PackageDescription
-> LocalBuildInfo -> UserHooks -> BuildFlags -> IO ()
PackageDescription
-> LocalBuildInfo -> UserHooks -> BuildFlags -> IO ()
bh
, replHook :: PackageDescription
-> LocalBuildInfo -> UserHooks -> ReplFlags -> [FilePath] -> IO ()
replHook = PackageDescription
-> LocalBuildInfo -> UserHooks -> ReplFlags -> [FilePath] -> IO ()
PackageDescription
-> LocalBuildInfo -> UserHooks -> ReplFlags -> [FilePath] -> IO ()
rh
, hscolourHook :: PackageDescription
-> LocalBuildInfo -> UserHooks -> HscolourFlags -> IO ()
hscolourHook = PackageDescription
-> LocalBuildInfo -> UserHooks -> HscolourFlags -> IO ()
PackageDescription
-> LocalBuildInfo -> UserHooks -> HscolourFlags -> IO ()
hscolourH
, doctestHook :: PackageDescription
-> LocalBuildInfo -> UserHooks -> DoctestFlags -> IO ()
doctestHook = PackageDescription
-> LocalBuildInfo -> UserHooks -> DoctestFlags -> IO ()
PackageDescription
-> LocalBuildInfo -> UserHooks -> DoctestFlags -> IO ()
dth
, haddockHook :: PackageDescription
-> LocalBuildInfo -> UserHooks -> HaddockFlags -> IO ()
haddockHook = PackageDescription
-> LocalBuildInfo -> UserHooks -> HaddockFlags -> IO ()
PackageDescription
-> LocalBuildInfo -> UserHooks -> HaddockFlags -> IO ()
hh
, copyHook :: PackageDescription
-> LocalBuildInfo -> UserHooks -> CopyFlags -> IO ()
copyHook = PackageDescription
-> LocalBuildInfo -> UserHooks -> CopyFlags -> IO ()
PackageDescription
-> LocalBuildInfo -> UserHooks -> CopyFlags -> IO ()
ch
, instHook :: PackageDescription
-> LocalBuildInfo -> UserHooks -> InstallFlags -> IO ()
instHook = PackageDescription
-> LocalBuildInfo -> UserHooks -> InstallFlags -> IO ()
PackageDescription
-> LocalBuildInfo -> UserHooks -> InstallFlags -> IO ()
ih
, testHook :: [FilePath]
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> TestFlags
-> IO ()
testHook = [FilePath]
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> TestFlags
-> IO ()
[FilePath]
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> TestFlags
-> IO ()
th
, benchHook :: [FilePath]
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> BenchmarkFlags
-> IO ()
benchHook = [FilePath]
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> BenchmarkFlags
-> IO ()
[FilePath]
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> BenchmarkFlags
-> IO ()
benchH
, regHook :: PackageDescription
-> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO ()
regHook = PackageDescription
-> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO ()
PackageDescription
-> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO ()
regH
, unregHook :: PackageDescription
-> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO ()
unregHook = PackageDescription
-> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO ()
PackageDescription
-> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO ()
unregH
}
where
bh :: PackageDescription -> LocalBuildInfo -> UserHooks -> BuildFlags -> IO ()
bh :: PackageDescription
-> LocalBuildInfo -> UserHooks -> BuildFlags -> IO ()
bh PackageDescription
pd LocalBuildInfo
lbi UserHooks
uhs BuildFlags
fs = do
PackageDescription
newPd <- HasCallStack =>
PackageDescription -> UserHooks -> IO PackageDescription
PackageDescription -> UserHooks -> IO PackageDescription
updatePackageDescription PackageDescription
pd UserHooks
uhs
(UserHooks
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> BuildFlags
-> IO ()
buildHook UserHooks
userHooks) PackageDescription
newPd LocalBuildInfo
lbi UserHooks
uhs BuildFlags
fs
rh :: PackageDescription -> LocalBuildInfo -> UserHooks -> ReplFlags -> [String] -> IO ()
rh :: PackageDescription
-> LocalBuildInfo -> UserHooks -> ReplFlags -> [FilePath] -> IO ()
rh PackageDescription
pd LocalBuildInfo
lbi UserHooks
uhs ReplFlags
fs [FilePath]
opts = do
PackageDescription
newPd <- HasCallStack =>
PackageDescription -> UserHooks -> IO PackageDescription
PackageDescription -> UserHooks -> IO PackageDescription
updatePackageDescription PackageDescription
pd UserHooks
uhs
(UserHooks
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> ReplFlags
-> [FilePath]
-> IO ()
replHook UserHooks
userHooks) PackageDescription
newPd LocalBuildInfo
lbi UserHooks
uhs ReplFlags
fs [FilePath]
opts
hscolourH :: PackageDescription -> LocalBuildInfo -> UserHooks -> HscolourFlags -> IO ()
hscolourH :: PackageDescription
-> LocalBuildInfo -> UserHooks -> HscolourFlags -> IO ()
hscolourH PackageDescription
pd LocalBuildInfo
lbi UserHooks
uhs HscolourFlags
fs = do
PackageDescription
newPd <- HasCallStack =>
PackageDescription -> UserHooks -> IO PackageDescription
PackageDescription -> UserHooks -> IO PackageDescription
updatePackageDescription PackageDescription
pd UserHooks
uhs
(UserHooks
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> HscolourFlags
-> IO ()
hscolourHook UserHooks
userHooks) PackageDescription
newPd LocalBuildInfo
lbi UserHooks
uhs HscolourFlags
fs
dth :: PackageDescription -> LocalBuildInfo -> UserHooks -> DoctestFlags -> IO ()
dth :: PackageDescription
-> LocalBuildInfo -> UserHooks -> DoctestFlags -> IO ()
dth PackageDescription
pd LocalBuildInfo
lbi UserHooks
uhs DoctestFlags
fs = do
PackageDescription
newPd <- HasCallStack =>
PackageDescription -> UserHooks -> IO PackageDescription
PackageDescription -> UserHooks -> IO PackageDescription
updatePackageDescription PackageDescription
pd UserHooks
uhs
(UserHooks
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> DoctestFlags
-> IO ()
doctestHook UserHooks
userHooks) PackageDescription
newPd LocalBuildInfo
lbi UserHooks
uhs DoctestFlags
fs
hh :: PackageDescription -> LocalBuildInfo -> UserHooks -> HaddockFlags -> IO ()
hh :: PackageDescription
-> LocalBuildInfo -> UserHooks -> HaddockFlags -> IO ()
hh PackageDescription
pd LocalBuildInfo
lbi UserHooks
uhs HaddockFlags
fs = do
PackageDescription
newPd <- HasCallStack =>
PackageDescription -> UserHooks -> IO PackageDescription
PackageDescription -> UserHooks -> IO PackageDescription
updatePackageDescription PackageDescription
pd UserHooks
uhs
(UserHooks
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> HaddockFlags
-> IO ()
haddockHook UserHooks
userHooks) PackageDescription
newPd LocalBuildInfo
lbi UserHooks
uhs HaddockFlags
fs
ch :: PackageDescription -> LocalBuildInfo -> UserHooks -> CopyFlags -> IO ()
ch :: PackageDescription
-> LocalBuildInfo -> UserHooks -> CopyFlags -> IO ()
ch PackageDescription
pd LocalBuildInfo
lbi UserHooks
uhs CopyFlags
fs = do
PackageDescription
newPd <- HasCallStack =>
PackageDescription -> UserHooks -> IO PackageDescription
PackageDescription -> UserHooks -> IO PackageDescription
updatePackageDescription PackageDescription
pd UserHooks
uhs
(UserHooks
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> CopyFlags
-> IO ()
copyHook UserHooks
userHooks) PackageDescription
newPd LocalBuildInfo
lbi UserHooks
uhs CopyFlags
fs
ih :: PackageDescription -> LocalBuildInfo -> UserHooks -> InstallFlags -> IO ()
ih :: PackageDescription
-> LocalBuildInfo -> UserHooks -> InstallFlags -> IO ()
ih PackageDescription
pd LocalBuildInfo
lbi UserHooks
uhs InstallFlags
fs = do
PackageDescription
newPd <- HasCallStack =>
PackageDescription -> UserHooks -> IO PackageDescription
PackageDescription -> UserHooks -> IO PackageDescription
updatePackageDescription PackageDescription
pd UserHooks
uhs
(UserHooks
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> InstallFlags
-> IO ()
instHook UserHooks
userHooks) PackageDescription
newPd LocalBuildInfo
lbi UserHooks
uhs InstallFlags
fs
th :: Args -> PackageDescription -> LocalBuildInfo -> UserHooks -> TestFlags -> IO ()
th :: [FilePath]
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> TestFlags
-> IO ()
th [FilePath]
args PackageDescription
pd LocalBuildInfo
lbi UserHooks
uhs TestFlags
fs = do
PackageDescription
newPd <- HasCallStack =>
PackageDescription -> UserHooks -> IO PackageDescription
PackageDescription -> UserHooks -> IO PackageDescription
updatePackageDescription PackageDescription
pd UserHooks
uhs
(UserHooks
-> [FilePath]
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> TestFlags
-> IO ()
testHook UserHooks
userHooks) [FilePath]
args PackageDescription
newPd LocalBuildInfo
lbi UserHooks
uhs TestFlags
fs
benchH :: Args -> PackageDescription -> LocalBuildInfo -> UserHooks -> BenchmarkFlags -> IO ()
benchH :: [FilePath]
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> BenchmarkFlags
-> IO ()
benchH [FilePath]
args PackageDescription
pd LocalBuildInfo
lbi UserHooks
uhs BenchmarkFlags
fs = do
PackageDescription
newPd <- HasCallStack =>
PackageDescription -> UserHooks -> IO PackageDescription
PackageDescription -> UserHooks -> IO PackageDescription
updatePackageDescription PackageDescription
pd UserHooks
uhs
(UserHooks
-> [FilePath]
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> BenchmarkFlags
-> IO ()
benchHook UserHooks
userHooks) [FilePath]
args PackageDescription
newPd LocalBuildInfo
lbi UserHooks
uhs BenchmarkFlags
fs
regH :: PackageDescription -> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO ()
regH :: PackageDescription
-> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO ()
regH PackageDescription
pd LocalBuildInfo
lbi UserHooks
uhs RegisterFlags
fs = do
PackageDescription
newPd <- HasCallStack =>
PackageDescription -> UserHooks -> IO PackageDescription
PackageDescription -> UserHooks -> IO PackageDescription
updatePackageDescription PackageDescription
pd UserHooks
uhs
(UserHooks
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> RegisterFlags
-> IO ()
regHook UserHooks
userHooks) PackageDescription
newPd LocalBuildInfo
lbi UserHooks
uhs RegisterFlags
fs
unregH :: PackageDescription -> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO ()
unregH :: PackageDescription
-> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO ()
unregH PackageDescription
pd LocalBuildInfo
lbi UserHooks
uhs RegisterFlags
fs = do
PackageDescription
newPd <- HasCallStack =>
PackageDescription -> UserHooks -> IO PackageDescription
PackageDescription -> UserHooks -> IO PackageDescription
updatePackageDescription PackageDescription
pd UserHooks
uhs
(UserHooks
-> PackageDescription
-> LocalBuildInfo
-> UserHooks
-> RegisterFlags
-> IO ()
unregHook UserHooks
userHooks) PackageDescription
newPd LocalBuildInfo
lbi UserHooks
uhs RegisterFlags
fs
sourceExtensions :: [String]
sourceExtensions :: [FilePath]
sourceExtensions = [FilePath
"hs",FilePath
"lhs"]
hsigExtensions :: [String]
hsigExtensions :: [FilePath]
hsigExtensions = [FilePath
"hsig",FilePath
"lhsig"]