diff --git a/Cabal/Distribution/Simple/Haddock.hs b/Cabal/Distribution/Simple/Haddock.hs index e36477e8e46e5fba7b0cdbe22cec2febebdfef88..a898250bd74d09312e49c60971da1f87d9feac78 100644 --- a/Cabal/Distribution/Simple/Haddock.hs +++ b/Cabal/Distribution/Simple/Haddock.hs @@ -91,7 +91,7 @@ import qualified Distribution.InstalledPackageInfo as InstalledPackageInfo import Distribution.InstalledPackageInfo ( InstalledPackageInfo ) import Distribution.Simple.Utils - ( die, warn, notice, intercalate, setupMessage + ( die, copyFileTo, warn, notice, intercalate, setupMessage , createDirectoryIfMissingVerbose, withTempFile, copyFileVerbose , withTempDirectory, matchFileGlob , findFileWithExtension, findFile ) @@ -112,7 +112,6 @@ import System.FilePath((</>), (<.>), splitFileName, splitExtension, normalise, splitPath, joinPath ) import System.IO (hClose, hPutStrLn) import Distribution.Version -import Distribution.Simple.SrcDist (copyFileTo) -- Types diff --git a/Cabal/Distribution/Simple/SrcDist.hs b/Cabal/Distribution/Simple/SrcDist.hs index 9698d5e0e0012184f9eb310c9c7019a722c9b056..797f1e20f82852c6d549f487d5cee4f17c10283c 100644 --- a/Cabal/Distribution/Simple/SrcDist.hs +++ b/Cabal/Distribution/Simple/SrcDist.hs @@ -70,14 +70,8 @@ module Distribution.Simple.SrcDist ( dateToSnapshotNumber, -- * Extracting the source files - findSetupFile, - findMainExeFile, - findIncludeFile, - filterAutogenModule, - allSourcesBuildInfo, - - -- * Utils - copyFileTo + listPackageSources + ) where import Distribution.PackageDescription @@ -94,7 +88,7 @@ import Distribution.Version ( Version(versionBranch) ) import Distribution.Simple.Utils ( createDirectoryIfMissingVerbose, withUTF8FileContents, writeUTF8File - , installOrdinaryFile, installOrdinaryFiles, setFileExecutable + , installOrdinaryFiles, installMaybeExecutableFiles , findFile, findFileWithExtension, matchFileGlob , withTempDirectory, defaultPackageDesc , die, warn, notice, setupMessage ) @@ -109,16 +103,15 @@ import Distribution.Simple.Program ( defaultProgramConfiguration, requireProgram import Distribution.Text ( display ) -import Control.Monad(when, unless, forM_) +import Control.Monad(when, unless, forM) import Data.Char (toLower) import Data.List (partition, isPrefixOf) import Data.Maybe (isNothing, catMaybes) import Data.Time (UTCTime, getCurrentTime, toGregorian, utctDay) -import System.Directory - ( doesFileExist, Permissions(executable), getPermissions ) +import System.Directory ( doesFileExist ) import Distribution.Verbosity (Verbosity) import System.FilePath - ( (</>), (<.>), takeDirectory, dropExtension, isAbsolute ) + ( (</>), (<.>), dropExtension, isAbsolute ) -- |Create a source distribution. sdist :: PackageDescription -- ^information from the tarball @@ -136,7 +129,7 @@ sdistWith :: PackageDescription -- ^information from the tarball -> Maybe LocalBuildInfo -- ^Information from configure -> SDistFlags -- ^verbosity & snapshot -> (FilePath -> FilePath) -- ^build prefix (temp dir) - -> [PPSuffixHandler] -- ^ extra preprocessors (includes + -> [PPSuffixHandler] -- ^extra preprocessors (includes -- suffixes) -> CreateArchiveFun -> IO () @@ -169,7 +162,7 @@ sdistWith pkg mb_lbi flags mkTmpDir pps createArchiveFun = do generateSourceDir targetDir pkg' = do setupMessage verbosity "Building source dist for" (packageId pkg') - prepareTree verbosity pkg' mb_lbi distPref targetDir pps + prepareTree verbosity pkg' mb_lbi targetDir pps when snapshot $ overwriteSnapshotPackageDesc verbosity pkg' targetDir @@ -181,95 +174,130 @@ sdistWith pkg mb_lbi flags mkTmpDir pps createArchiveFun = do tmpTargetDir = mkTmpDir distPref +-- | List all source files of a package. Returns a tuple of lists: first +-- component is a list of ordinary files, second one is a list of those files +-- that may be executable. +listPackageSources :: Verbosity -- ^ verbosity + -> PackageDescription -- ^ info from the cabal file + -> [PPSuffixHandler] -- ^ extra preprocessors (include + -- suffixes) + -> IO ([FilePath], [FilePath]) +listPackageSources verbosity pkg_descr0 pps = do + -- Call helpers that actually do all work. + ordinary <- listPackageSourcesOrdinary verbosity pkg_descr pps + maybeExecutable <- listPackageSourcesMaybeExecutable pkg_descr + return (ordinary, maybeExecutable) + where + pkg_descr = filterAutogenModule pkg_descr0 + +-- | List those source files that may be executable (e.g. the configure script). +listPackageSourcesMaybeExecutable :: PackageDescription -> IO [FilePath] +listPackageSourcesMaybeExecutable pkg_descr = + -- Extra source files. + fmap concat . forM (extraSrcFiles pkg_descr) $ \fpath -> matchFileGlob fpath + +-- | List those source files that should be copied with ordinary permissions. +listPackageSourcesOrdinary :: Verbosity + -> PackageDescription + -> [PPSuffixHandler] + -> IO [FilePath] +listPackageSourcesOrdinary verbosity pkg_descr pps = + fmap concat . sequence $ + [ + -- Library sources. + withLib $ \Library { exposedModules = modules, libBuildInfo = libBi } -> + allSourcesBuildInfo libBi pps modules + + -- Executables sources. + , fmap concat + . withExe $ \Executable { modulePath = mainPath, buildInfo = exeBi } -> do + biSrcs <- allSourcesBuildInfo exeBi pps [] + mainSrc <- findMainExeFile exeBi pps mainPath + return (mainSrc:biSrcs) + + -- Test suites sources. + , fmap concat + . withTest $ \t -> do + let bi = testBuildInfo t + case testInterface t of + TestSuiteExeV10 _ mainPath -> do + biSrcs <- allSourcesBuildInfo bi pps [] + srcMainFile <- do + ppFile <- findFileWithExtension (ppSuffixes pps) + (hsSourceDirs bi) (dropExtension mainPath) + case ppFile of + Nothing -> findFile (hsSourceDirs bi) mainPath + Just pp -> return pp + return (srcMainFile:biSrcs) + TestSuiteLibV09 _ m -> + allSourcesBuildInfo bi pps [m] + TestSuiteUnsupported tp -> die $ "Unsupported test suite type: " + ++ show tp + + -- Benchmarks sources. + , fmap concat + . withBenchmark $ \bm -> do + let bi = benchmarkBuildInfo bm + case benchmarkInterface bm of + BenchmarkExeV10 _ mainPath -> do + biSrcs <- allSourcesBuildInfo bi pps [] + srcMainFile <- do + ppFile <- findFileWithExtension (ppSuffixes pps) + (hsSourceDirs bi) (dropExtension mainPath) + case ppFile of + Nothing -> findFile (hsSourceDirs bi) mainPath + Just pp -> return pp + return (srcMainFile:biSrcs) + BenchmarkUnsupported tp -> die $ "Unsupported benchmark type: " + ++ show tp + + -- Data files. + , fmap concat + . forM (dataFiles pkg_descr) $ \filename -> + matchFileGlob (dataDir pkg_descr </> filename) + + -- License file. + , return $ case [licenseFile pkg_descr] + of [[]] -> [] + l -> l + -- Install-include files. + , withLib $ \ l -> do + let lbi = libBuildInfo l + relincdirs = "." : filter (not.isAbsolute) (includeDirs lbi) + mapM (fmap snd . findIncludeFile relincdirs) (installIncludes lbi) + + -- Setup script. + , do mSetupFile <- findSetupFile + case mSetupFile of + Just setupFile -> return [setupFile] + Nothing -> do writeUTF8File "Setup.hs" $ unlines [ + "import Distribution.Simple", + "main = defaultMain"] + return ["Setup.hs"] + + -- The .cabal file itself. + , fmap (\d -> [d]) (defaultPackageDesc verbosity) + + ] + where + -- We have to deal with all libs and executables, so we have local + -- versions of these functions that ignore the 'buildable' attribute: + withLib action = maybe (return []) action (library pkg_descr) + withExe action = mapM action (executables pkg_descr) + withTest action = mapM action (testSuites pkg_descr) + withBenchmark action = mapM action (benchmarks pkg_descr) + + -- |Prepare a directory tree of source files. prepareTree :: Verbosity -- ^verbosity -> PackageDescription -- ^info from the cabal file -> Maybe LocalBuildInfo - -> FilePath -- ^dist dir -> FilePath -- ^source tree to populate -> [PPSuffixHandler] -- ^extra preprocessors (includes suffixes) -> IO () -prepareTree verbosity pkg_descr0 mb_lbi distPref targetDir pps = do - createDirectoryIfMissingVerbose verbosity True targetDir - - -- maybe move the library files into place - withLib $ \Library { exposedModules = modules, libBuildInfo = libBi } -> - prepareDir verbosity pkg_descr distPref targetDir pps modules libBi - - -- move the executables into place - withExe $ \Executable { modulePath = mainPath, buildInfo = exeBi } -> do - prepareDir verbosity pkg_descr distPref targetDir pps [] exeBi - srcMainFile <- findMainExeFile exeBi pps mainPath - copyFileTo verbosity targetDir srcMainFile - - -- move the test suites into place - withTest $ \t -> do - let bi = testBuildInfo t - prep = prepareDir verbosity pkg_descr distPref targetDir pps - case testInterface t of - TestSuiteExeV10 _ mainPath -> do - prep [] bi - srcMainFile <- do - ppFile <- findFileWithExtension (ppSuffixes pps) - (hsSourceDirs bi) - (dropExtension mainPath) - case ppFile of - Nothing -> findFile (hsSourceDirs bi) mainPath - Just pp -> return pp - copyFileTo verbosity targetDir srcMainFile - TestSuiteLibV09 _ m -> do - prep [m] bi - TestSuiteUnsupported tp -> die $ "Unsupported test suite type: " - ++ show tp - - -- move the benchmarks into place - withBenchmark $ \bm -> do - let bi = benchmarkBuildInfo bm - prep = prepareDir verbosity pkg_descr distPref targetDir pps - case benchmarkInterface bm of - BenchmarkExeV10 _ mainPath -> do - prep [] bi - srcMainFile <- do - ppFile <- findFileWithExtension (ppSuffixes pps) - (hsSourceDirs bi) - (dropExtension mainPath) - case ppFile of - Nothing -> findFile (hsSourceDirs bi) mainPath - Just pp -> return pp - copyFileTo verbosity targetDir srcMainFile - BenchmarkUnsupported tp -> die $ "Unsupported benchmark type: " - ++ show tp - - -- move the data files into place. - forM_ (dataFiles pkg_descr) $ \ filename -> do - files <- matchFileGlob (dataDir pkg_descr </> filename) - let dir = takeDirectory (dataDir pkg_descr </> filename) - createDirectoryIfMissingVerbose verbosity True (targetDir </> dir) - sequence_ [ installOrdinaryFile verbosity file (targetDir </> file) - | file <- files ] - - -- move the license file and extra src files into place. - when (not (null (licenseFile pkg_descr))) $ - copyFileTo verbosity targetDir (licenseFile pkg_descr) - forM_ (extraSrcFiles pkg_descr ++ extraHtmlFiles pkg_descr) $ \ fpath -> do - files <- matchFileGlob fpath - sequence_ - [ do copyFileTo verbosity targetDir file - -- preserve executable bit on extra-src-files like ./configure - perms <- getPermissions file - when (executable perms) --only checks user x bit - (setFileExecutable (targetDir </> file)) - | file <- files ] - - -- copy the install-include files - withLib $ \ l -> do - let lbi = libBuildInfo l - relincdirs = "." : filter (not.isAbsolute) (includeDirs lbi) - incs <- mapM (findIncludeFile relincdirs) (installIncludes lbi) - forM_ incs $ \(_,fpath) -> copyFileTo verbosity targetDir fpath - - -- if the package was configured then we can run platform independent - -- pre-processors and include those generated files +prepareTree verbosity pkg_descr0 mb_lbi targetDir pps = do + -- If the package was configured then we can run platform independent + -- pre-processors and include those generated files. case mb_lbi of Just lbi | not (null pps) -> do let lbi' = lbi{ buildDir = targetDir </> buildDir lbi } @@ -277,28 +305,13 @@ prepareTree verbosity pkg_descr0 mb_lbi distPref targetDir pps = do preprocessComponent pkg_descr c lbi' True verbosity pps _ -> return () - -- setup isn't listed in the description file. - mSetupFile <- findSetupFile - case mSetupFile of - Just setupFile -> copyFileTo verbosity targetDir setupFile - Nothing -> do writeUTF8File (targetDir </> "Setup.hs") $ unlines [ - "import Distribution.Simple", - "main = defaultMain"] - - -- the description file itself - descFile <- defaultPackageDesc verbosity - installOrdinaryFile verbosity descFile (targetDir </> descFile) + (ordinary, mExecutable) <- listPackageSources verbosity pkg_descr0 pps + installOrdinaryFiles verbosity targetDir (zip (repeat []) ordinary) + installMaybeExecutableFiles verbosity targetDir (zip (repeat []) mExecutable) where pkg_descr = filterAutogenModule pkg_descr0 - -- We have to deal with all libs and executables, so we have local - -- versions of these functions that ignore the 'buildable' attribute: - withLib action = maybe (return ()) action (library pkg_descr) - withExe action = mapM_ action (executables pkg_descr) - withTest action = mapM_ action (testSuites pkg_descr) - withBenchmark action = mapM_ action (benchmarks pkg_descr) - -- | Find the setup script file, if it exists. findSetupFile :: IO (Maybe FilePath) findSetupFile = do @@ -354,13 +367,12 @@ filterAutogenModule pkg_descr0 = mapLib filterAutogenModuleLib $ prepareSnapshotTree :: Verbosity -- ^verbosity -> PackageDescription -- ^info from the cabal file -> Maybe LocalBuildInfo - -> FilePath -- ^dist dir -> FilePath -- ^source tree to populate -> [PPSuffixHandler] -- ^extra preprocessors (includes -- suffixes) -> IO () -prepareSnapshotTree verbosity pkg mb_lbi distPref targetDir pps = do - prepareTree verbosity pkg mb_lbi distPref targetDir pps +prepareSnapshotTree verbosity pkg mb_lbi targetDir pps = do + prepareTree verbosity pkg mb_lbi targetDir pps overwriteSnapshotPackageDesc verbosity pkg targetDir overwriteSnapshotPackageDesc :: Verbosity -- ^verbosity @@ -435,19 +447,6 @@ createArchive verbosity pkg_descr mb_lbi tmpDir targetPref = do ["-C", tmpDir, "-czf", tarBallFilePath, tarBallName pkg_descr] return tarBallFilePath --- |Move the sources into place based on buildInfo -prepareDir :: Verbosity -- ^ verbosity - -> PackageDescription -- ^ info from the cabal file - -> FilePath -- ^ dist dir - -> FilePath -- ^ TargetPrefix - -> [PPSuffixHandler] -- ^ extra preprocessors (includes suffixes) - -> [ModuleName] -- ^ Exposed modules - -> BuildInfo - -> IO () -prepareDir verbosity _pkg _distPref inPref pps modules bi - = do allSources <- allSourcesBuildInfo bi pps modules - installOrdinaryFiles verbosity inPref (zip (repeat []) allSources) - -- | Given a buildinfo, return the names of all source files. allSourcesBuildInfo :: BuildInfo -> [PPSuffixHandler] -- ^ Extra preprocessors @@ -474,12 +473,6 @@ allSourcesBuildInfo bi pps modules = do ++ " with any suffix: " ++ show suffixes -copyFileTo :: Verbosity -> FilePath -> FilePath -> IO () -copyFileTo verbosity dir file = do - let targetFile = dir </> file - createDirectoryIfMissingVerbose verbosity True (takeDirectory targetFile) - installOrdinaryFile verbosity file targetFile - printPackageProblems :: Verbosity -> PackageDescription -> IO () printPackageProblems verbosity pkg_descr = do ioChecks <- checkPackageFiles pkg_descr "." diff --git a/Cabal/Distribution/Simple/Utils.hs b/Cabal/Distribution/Simple/Utils.hs index c5385cce09d0b4e72546f82b9de14a47e9399171..82a17638a49809bdd89736590d157779d20e6f0a 100644 --- a/Cabal/Distribution/Simple/Utils.hs +++ b/Cabal/Distribution/Simple/Utils.hs @@ -72,11 +72,15 @@ module Distribution.Simple.Utils ( copyFileVerbose, copyDirectoryRecursiveVerbose, copyFiles, + copyFileTo, -- * installing files installOrdinaryFile, installExecutableFile, + installMaybeExecutableFile, installOrdinaryFiles, + installExecutableFiles, + installMaybeExecutableFiles, installDirectoryContents, -- * File permissions @@ -151,8 +155,8 @@ import qualified Data.ByteString.Lazy as BS import qualified Data.ByteString.Lazy.Char8 as BS.Char8 import System.Directory - ( getDirectoryContents, doesDirectoryExist, doesFileExist, removeFile - , findExecutable ) + ( Permissions(executable), getDirectoryContents, getPermissions + , doesDirectoryExist, doesFileExist, removeFile, findExecutable ) import System.Environment ( getProgName ) import System.Cmd @@ -796,6 +800,38 @@ installExecutableFile verbosity src dest = do info verbosity ("Installing executable " ++ src ++ " to " ++ dest) copyExecutableFile src dest +-- | Install a file that may or not be executable, preserving permissions. +installMaybeExecutableFile :: Verbosity -> FilePath -> FilePath -> IO () +installMaybeExecutableFile verbosity src dest = do + perms <- getPermissions src + if (executable perms) --only checks user x bit + then installExecutableFile verbosity src dest + else installOrdinaryFile verbosity src dest + +-- | Given a relative path to a file, copy it to the given directory, preserving +-- the relative path and creating the parent directories if needed. +copyFileTo :: Verbosity -> FilePath -> FilePath -> IO () +copyFileTo verbosity dir file = do + let targetFile = dir </> file + createDirectoryIfMissingVerbose verbosity True (takeDirectory targetFile) + installOrdinaryFile verbosity file targetFile + +-- | Common implementation of 'copyFiles', 'installOrdinaryFiles', +-- 'installExecutableFiles' and 'installMaybeExecutableFiles'. +copyFilesWith :: (Verbosity -> FilePath -> FilePath -> IO ()) + -> Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO () +copyFilesWith doCopy verbosity targetDir srcFiles = do + + -- Create parent directories for everything + let dirs = map (targetDir </>) . nub . map (takeDirectory . snd) $ srcFiles + mapM_ (createDirectoryIfMissingVerbose verbosity True) dirs + + -- Copy all the files + sequence_ [ let src = srcBase </> srcFile + dest = targetDir </> srcFile + in doCopy verbosity src dest + | (srcBase, srcFile) <- srcFiles ] + -- | Copies a bunch of files to a target directory, preserving the directory -- structure in the target location. The target directories are created if they -- do not exist. @@ -818,32 +854,24 @@ installExecutableFile verbosity src dest = do -- anything goes wrong. -- copyFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO () -copyFiles verbosity targetDir srcFiles = do - - -- Create parent directories for everything - let dirs = map (targetDir </>) . nub . map (takeDirectory . snd) $ srcFiles - mapM_ (createDirectoryIfMissingVerbose verbosity True) dirs - - -- Copy all the files - sequence_ [ let src = srcBase </> srcFile - dest = targetDir </> srcFile - in copyFileVerbose verbosity src dest - | (srcBase, srcFile) <- srcFiles ] +copyFiles = copyFilesWith copyFileVerbose -- | This is like 'copyFiles' but uses 'installOrdinaryFile'. -- installOrdinaryFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO () -installOrdinaryFiles verbosity targetDir srcFiles = do +installOrdinaryFiles = copyFilesWith installOrdinaryFile - -- Create parent directories for everything - let dirs = map (targetDir </>) . nub . map (takeDirectory . snd) $ srcFiles - mapM_ (createDirectoryIfMissingVerbose verbosity True) dirs +-- | This is like 'copyFiles' but uses 'installExecutableFile'. +-- +installExecutableFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] + -> IO () +installExecutableFiles = copyFilesWith installExecutableFile - -- Copy all the files - sequence_ [ let src = srcBase </> srcFile - dest = targetDir </> srcFile - in installOrdinaryFile verbosity src dest - | (srcBase, srcFile) <- srcFiles ] +-- | This is like 'copyFiles' but uses 'installMaybeExecutableFile'. +-- +installMaybeExecutableFiles :: Verbosity -> FilePath -> [(FilePath, FilePath)] + -> IO () +installMaybeExecutableFiles = copyFilesWith installMaybeExecutableFile -- | This installs all the files in a directory to a target location, -- preserving the directory layout. All the files are assumed to be ordinary diff --git a/cabal-install/Distribution/Client/Sandbox.hs b/cabal-install/Distribution/Client/Sandbox.hs index 38c8d51bec10bb39fce0256d083160ded65f12b4..ccafb4f89de100693e38cc4c09ec45d29d0a52da 100644 --- a/cabal-install/Distribution/Client/Sandbox.hs +++ b/cabal-install/Distribution/Client/Sandbox.hs @@ -316,8 +316,7 @@ sandboxAddSourceSnapshot verbosity buildTreeRefs sandboxDir pkgEnv = do when dirExists $ removeDirectoryRecursive targetDir createDirectory targetTmpDir - prepareTree verbosity pkg Nothing buildTreeRef targetTmpDir - knownSuffixHandlers + prepareTree verbosity pkg Nothing targetTmpDir knownSuffixHandlers return (targetTmpDir, targetDir) -- Now rename the "snapshots/$PKGNAME-$VERSION-tmp" dirs to diff --git a/cabal-install/Distribution/Client/Sandbox/Timestamp.hs b/cabal-install/Distribution/Client/Sandbox/Timestamp.hs index 5e7698935fade988712b1b3621960329258bb186..3536a4425b003117b23ec98d901f5651ff02b474 100644 --- a/cabal-install/Distribution/Client/Sandbox/Timestamp.hs +++ b/cabal-install/Distribution/Client/Sandbox/Timestamp.hs @@ -20,26 +20,16 @@ module Distribution.Client.Sandbox.Timestamp ( import Control.Monad (filterM, forM, when) import Data.Char (isSpace) import Data.List (partition) -import Data.Maybe (maybeToList) import System.Directory (renameFile) -import System.FilePath (isAbsolute, (<.>), (</>)) +import System.FilePath ((<.>), (</>)) import Distribution.Compiler (CompilerId) -import Distribution.PackageDescription (BuildInfo (..), - Executable (..), - Library (..), - PackageDescription (..)) import Distribution.PackageDescription.Configuration (flattenPackageDescription) import Distribution.PackageDescription.Parse (readPackageDescription) import Distribution.Simple.PreProcess (knownSuffixHandlers) -import Distribution.Simple.SrcDist (allSourcesBuildInfo, - filterAutogenModule, - findIncludeFile, - findMainExeFile, - findSetupFile) -import Distribution.Simple.Utils (defaultPackageDesc, die, - debug, findPackageDesc, - matchFileGlob, warn) +import Distribution.Simple.SrcDist (listPackageSources) +import Distribution.Simple.Utils (die, debug, + findPackageDesc, warn) import Distribution.System (Platform) import Distribution.Text (display) import Distribution.Verbosity (Verbosity) @@ -212,45 +202,12 @@ withActionOnCompilerTimestamps f sandboxDir compId platform act = do -- FIXME: This function is not thread-safe because of 'inDir'. allPackageSourceFiles :: Verbosity -> FilePath -> IO [FilePath] allPackageSourceFiles verbosity packageDir = inDir (Just packageDir) $ do - pkgDesc <- fmap (filterAutogenModule . flattenPackageDescription) + pkgDesc <- fmap (flattenPackageDescription) . readPackageDescription verbosity =<< findPackageDesc packageDir - -- NOTE: This is patterned after "Distribution.Simple.SrcDist.prepareTree". - libSources <- withLib pkgDesc $ - \Library { exposedModules = modules, libBuildInfo = libBi } -> - allSourcesBuildInfo libBi pps modules - exeSources <- withExe pkgDesc $ - \Executable { modulePath = mainPath, buildInfo = exeBi } -> do - biSrcs <- allSourcesBuildInfo exeBi pps [] - mainSrc <- findMainExeFile exeBi pps mainPath - return (mainSrc:biSrcs) - - -- We don't care about test and benchmark sources. - - dataFs <- forM (dataFiles pkgDesc) $ \filename -> - matchFileGlob (dataDir pkgDesc </> filename) - - extraSrcs <- forM (extraSrcFiles pkgDesc) $ \fpath -> - matchFileGlob fpath - - incFiles <- withLib pkgDesc $ \ l -> do - let lbi = libBuildInfo l - relincdirs = "." : filter (not.isAbsolute) (includeDirs lbi) - mapM (fmap snd . findIncludeFile relincdirs) (installIncludes lbi) - - mSetupFile <- findSetupFile - descFile <- defaultPackageDesc verbosity - - mapM tryCanonicalizePath . map (packageDir </>) $ - descFile : (maybeToList mSetupFile) - ++ incFiles ++ (concat extraSrcs) ++ (concat dataFs) - ++ (concat exeSources) ++ libSources + (ordinary, executable) <- listPackageSources verbosity pkgDesc pps + mapM tryCanonicalizePath (executable ++ ordinary) where - -- We have to deal with all libs and executables, so we have local - -- versions of these functions that ignore the 'buildable' attribute: - withLib pkgDesc action = maybe (return []) action (library pkgDesc) - withExe pkgDesc action = mapM action (executables pkgDesc) - pps = knownSuffixHandlers