{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  Distribution.Simple.SrcDist
-- Copyright   :  Simon Marlow 2004
-- License     :  BSD3
--
-- Maintainer  :  cabal-devel@haskell.org
-- Portability :  portable
--
-- This handles the @sdist@ command. The module exports an 'sdist' action but
-- also some of the phases that make it up so that other tools can use just the
-- bits they need. In particular the preparation of the tree of files to go
-- into the source tarball is separated from actually building the source
-- tarball.
--
-- The 'createArchive' action uses the external @tar@ program and assumes that
-- it accepts the @-z@ flag. Neither of these assumptions are valid on Windows.
-- The 'sdist' action now also does some distribution QA checks.

-- NOTE: FIX: we don't have a great way of testing this module, since
-- we can't easily look inside a tarball once its created.

module Distribution.Simple.SrcDist (
  -- * The top level action
  sdist,

  -- ** Parts of 'sdist'
  printPackageProblems,
  prepareTree,
  createArchive,

  -- ** Snapshots
  prepareSnapshotTree,
  snapshotPackage,
  snapshotVersion,
  dateToSnapshotNumber,

  -- * Extracting the source files
  listPackageSources

  )  where

import Prelude ()
import Distribution.Compat.Prelude

import Distribution.PackageDescription hiding (Flag)
import Distribution.PackageDescription.Check hiding (doesFileExist)
import Distribution.Package
import Distribution.ModuleName
import qualified Distribution.ModuleName as ModuleName
import Distribution.Version
import Distribution.Simple.Configure (findDistPrefOrDefault)
import Distribution.Simple.Glob
import Distribution.Simple.Utils
import Distribution.Simple.Setup
import Distribution.Simple.PreProcess
import Distribution.Simple.LocalBuildInfo
import Distribution.Simple.BuildPaths
import Distribution.Simple.Program
import Distribution.Pretty
import Distribution.Types.ForeignLib
import Distribution.Verbosity

import Data.List (partition)
import qualified Data.Map as Map
import Data.Time (UTCTime, getCurrentTime, toGregorian, utctDay)
import System.Directory ( doesFileExist )
import System.IO (IOMode(WriteMode), hPutStrLn, withFile)
import System.FilePath ((</>), (<.>), dropExtension, isRelative)
import Control.Monad

-- |Create a source distribution.
sdist :: PackageDescription     -- ^information from the tarball
      -> Maybe LocalBuildInfo   -- ^Information from configure
      -> SDistFlags             -- ^verbosity & snapshot
      -> (FilePath -> FilePath) -- ^build prefix (temp dir)
      -> [PPSuffixHandler]      -- ^ extra preprocessors (includes suffixes)
      -> IO ()
sdist :: PackageDescription
-> Maybe LocalBuildInfo
-> SDistFlags
-> (FilePath -> FilePath)
-> [PPSuffixHandler]
-> IO ()
sdist PackageDescription
pkg Maybe LocalBuildInfo
mb_lbi SDistFlags
flags FilePath -> FilePath
mkTmpDir [PPSuffixHandler]
pps = do

  FilePath
distPref <- Flag FilePath -> NoCallStackIO FilePath
findDistPrefOrDefault (Flag FilePath -> NoCallStackIO FilePath)
-> Flag FilePath -> NoCallStackIO FilePath
forall a b. (a -> b) -> a -> b
$ SDistFlags -> Flag FilePath
sDistDistPref SDistFlags
flags
  let targetPref :: FilePath
targetPref   = FilePath
distPref
      tmpTargetDir :: FilePath
tmpTargetDir = FilePath -> FilePath
mkTmpDir FilePath
distPref

  -- When given --list-sources, just output the list of sources to a file.
  case (SDistFlags -> Flag FilePath
sDistListSources SDistFlags
flags) of
    Flag FilePath
path -> FilePath -> IOMode -> (Handle -> IO ()) -> IO ()
forall r. FilePath -> IOMode -> (Handle -> IO r) -> IO r
withFile FilePath
path IOMode
WriteMode ((Handle -> IO ()) -> IO ()) -> (Handle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Handle
outHandle -> do
      ([FilePath]
ordinary, [FilePath]
maybeExecutable) <- Verbosity
-> PackageDescription
-> [PPSuffixHandler]
-> IO ([FilePath], [FilePath])
listPackageSources Verbosity
verbosity PackageDescription
pkg [PPSuffixHandler]
pps
      (FilePath -> IO ()) -> [FilePath] -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ (Handle -> FilePath -> IO ()
hPutStrLn Handle
outHandle) [FilePath]
ordinary
      (FilePath -> IO ()) -> [FilePath] -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ (Handle -> FilePath -> IO ()
hPutStrLn Handle
outHandle) [FilePath]
maybeExecutable
      Verbosity -> FilePath -> IO ()
notice Verbosity
verbosity (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"List of package sources written to file '"
                         FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
path FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"'"
    Flag FilePath
NoFlag    -> do
      -- do some QA
      Verbosity -> PackageDescription -> IO ()
printPackageProblems Verbosity
verbosity PackageDescription
pkg

      Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Maybe LocalBuildInfo -> Bool
forall a. Maybe a -> Bool
isNothing Maybe LocalBuildInfo
mb_lbi) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
        Verbosity -> FilePath -> IO ()
warn Verbosity
verbosity FilePath
"Cannot run preprocessors. Run 'configure' command first."

      UTCTime
date <- IO UTCTime
getCurrentTime
      let pkg' :: PackageDescription
pkg' | Bool
snapshot  = UTCTime -> PackageDescription -> PackageDescription
snapshotPackage UTCTime
date PackageDescription
pkg
               | Bool
otherwise = PackageDescription
pkg

      case Flag FilePath -> Maybe FilePath
forall a. Flag a -> Maybe a
flagToMaybe (SDistFlags -> Flag FilePath
sDistDirectory SDistFlags
flags) of
        Just FilePath
targetDir -> do
          FilePath -> PackageDescription -> IO ()
generateSourceDir FilePath
targetDir PackageDescription
pkg'
          Verbosity -> FilePath -> IO ()
info Verbosity
verbosity (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"Source directory created: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
targetDir

        Maybe FilePath
Nothing -> do
          Verbosity -> Bool -> FilePath -> IO ()
createDirectoryIfMissingVerbose Verbosity
verbosity Bool
True FilePath
tmpTargetDir
          Verbosity -> FilePath -> FilePath -> (FilePath -> IO ()) -> IO ()
forall a.
Verbosity -> FilePath -> FilePath -> (FilePath -> IO a) -> IO a
withTempDirectory Verbosity
verbosity FilePath
tmpTargetDir FilePath
"sdist." ((FilePath -> IO ()) -> IO ()) -> (FilePath -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \FilePath
tmpDir -> do
            let targetDir :: FilePath
targetDir = FilePath
tmpDir FilePath -> FilePath -> FilePath
</> PackageDescription -> FilePath
tarBallName PackageDescription
pkg'
            FilePath -> PackageDescription -> IO ()
generateSourceDir FilePath
targetDir PackageDescription
pkg'
            FilePath
targzFile <- CreateArchiveFun
createArchive Verbosity
verbosity PackageDescription
pkg' Maybe LocalBuildInfo
mb_lbi FilePath
tmpDir FilePath
targetPref
            Verbosity -> FilePath -> IO ()
notice Verbosity
verbosity (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"Source tarball created: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
targzFile

  where
    generateSourceDir :: FilePath -> PackageDescription -> IO ()
generateSourceDir FilePath
targetDir PackageDescription
pkg' = do

      Verbosity -> FilePath -> PackageIdentifier -> IO ()
setupMessage Verbosity
verbosity FilePath
"Building source dist for" (PackageDescription -> PackageIdentifier
forall pkg. Package pkg => pkg -> PackageIdentifier
packageId PackageDescription
pkg')
      Verbosity
-> PackageDescription
-> Maybe LocalBuildInfo
-> FilePath
-> [PPSuffixHandler]
-> IO ()
prepareTree Verbosity
verbosity PackageDescription
pkg' Maybe LocalBuildInfo
mb_lbi FilePath
targetDir [PPSuffixHandler]
pps
      Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
snapshot (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
        Verbosity -> PackageDescription -> FilePath -> IO ()
overwriteSnapshotPackageDesc Verbosity
verbosity PackageDescription
pkg' FilePath
targetDir

    verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (SDistFlags -> Flag Verbosity
sDistVerbosity SDistFlags
flags)
    snapshot :: Bool
snapshot  = Flag Bool -> Bool
forall a. WithCallStack (Flag a -> a)
fromFlag (SDistFlags -> Flag Bool
sDistSnapshot SDistFlags
flags)

-- | 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
-> PackageDescription
-> [PPSuffixHandler]
-> IO ([FilePath], [FilePath])
listPackageSources Verbosity
verbosity PackageDescription
pkg_descr0 [PPSuffixHandler]
pps = do
  -- Call helpers that actually do all work.
  [FilePath]
ordinary        <- Verbosity
-> PackageDescription -> [PPSuffixHandler] -> IO [FilePath]
listPackageSourcesOrdinary        Verbosity
verbosity PackageDescription
pkg_descr [PPSuffixHandler]
pps
  [FilePath]
maybeExecutable <- Verbosity -> PackageDescription -> IO [FilePath]
listPackageSourcesMaybeExecutable Verbosity
verbosity PackageDescription
pkg_descr
  ([FilePath], [FilePath]) -> IO ([FilePath], [FilePath])
forall (m :: * -> *) a. Monad m => a -> m a
return ([FilePath]
ordinary, [FilePath]
maybeExecutable)
  where
    pkg_descr :: PackageDescription
pkg_descr = PackageDescription -> PackageDescription
filterAutogenModules PackageDescription
pkg_descr0

-- | List those source files that may be executable (e.g. the configure script).
listPackageSourcesMaybeExecutable :: Verbosity -> PackageDescription -> IO [FilePath]
listPackageSourcesMaybeExecutable :: Verbosity -> PackageDescription -> IO [FilePath]
listPackageSourcesMaybeExecutable Verbosity
verbosity PackageDescription
pkg_descr =
  -- Extra source files.
  ([[FilePath]] -> [FilePath]) -> IO [[FilePath]] -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [[FilePath]] -> [FilePath]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (IO [[FilePath]] -> IO [FilePath])
-> ((FilePath -> IO [FilePath]) -> IO [[FilePath]])
-> (FilePath -> IO [FilePath])
-> IO [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> (FilePath -> IO [FilePath]) -> IO [[FilePath]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for (PackageDescription -> [FilePath]
extraSrcFiles PackageDescription
pkg_descr) ((FilePath -> IO [FilePath]) -> IO [FilePath])
-> (FilePath -> IO [FilePath]) -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ \FilePath
fpath ->
    Verbosity -> Version -> FilePath -> FilePath -> IO [FilePath]
matchDirFileGlob Verbosity
verbosity (PackageDescription -> Version
specVersion PackageDescription
pkg_descr) FilePath
"." FilePath
fpath

-- | List those source files that should be copied with ordinary permissions.
listPackageSourcesOrdinary :: Verbosity
                           -> PackageDescription
                           -> [PPSuffixHandler]
                           -> IO [FilePath]
listPackageSourcesOrdinary :: Verbosity
-> PackageDescription -> [PPSuffixHandler] -> IO [FilePath]
listPackageSourcesOrdinary Verbosity
verbosity PackageDescription
pkg_descr [PPSuffixHandler]
pps =
  ([[FilePath]] -> [FilePath]) -> IO [[FilePath]] -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [[FilePath]] -> [FilePath]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (IO [[FilePath]] -> IO [FilePath])
-> ([IO [FilePath]] -> IO [[FilePath]])
-> [IO [FilePath]]
-> IO [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [IO [FilePath]] -> IO [[FilePath]]
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA ([IO [FilePath]] -> IO [FilePath])
-> [IO [FilePath]] -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$
  [
    -- Library sources.
    ([[FilePath]] -> [FilePath]) -> IO [[FilePath]] -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [[FilePath]] -> [FilePath]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
    (IO [[FilePath]] -> IO [FilePath])
-> ((Library -> IO [FilePath]) -> IO [[FilePath]])
-> (Library -> IO [FilePath])
-> IO [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Library -> IO [FilePath]) -> IO [[FilePath]]
forall (f :: * -> *) b. Applicative f => (Library -> f b) -> f [b]
withAllLib ((Library -> IO [FilePath]) -> IO [FilePath])
-> (Library -> IO [FilePath]) -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ \Library {
                      exposedModules :: Library -> [ModuleName]
exposedModules = [ModuleName]
modules,
                      signatures :: Library -> [ModuleName]
signatures     = [ModuleName]
sigs,
                      libBuildInfo :: Library -> BuildInfo
libBuildInfo   = BuildInfo
libBi
                    } ->
     Verbosity
-> BuildInfo -> [PPSuffixHandler] -> [ModuleName] -> IO [FilePath]
allSourcesBuildInfo Verbosity
verbosity BuildInfo
libBi [PPSuffixHandler]
pps ([ModuleName]
modules [ModuleName] -> [ModuleName] -> [ModuleName]
forall a. [a] -> [a] -> [a]
++ [ModuleName]
sigs)

    -- Executables sources.
  , ([[FilePath]] -> [FilePath]) -> IO [[FilePath]] -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [[FilePath]] -> [FilePath]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
    (IO [[FilePath]] -> IO [FilePath])
-> ((Executable -> IO [FilePath]) -> IO [[FilePath]])
-> (Executable -> IO [FilePath])
-> IO [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Executable -> IO [FilePath]) -> IO [[FilePath]]
forall (f :: * -> *) b.
Applicative f =>
(Executable -> f b) -> f [b]
withAllExe ((Executable -> IO [FilePath]) -> IO [FilePath])
-> (Executable -> IO [FilePath]) -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ \Executable { modulePath :: Executable -> FilePath
modulePath = FilePath
mainPath, buildInfo :: Executable -> BuildInfo
buildInfo = BuildInfo
exeBi } -> do
       [FilePath]
biSrcs  <- Verbosity
-> BuildInfo -> [PPSuffixHandler] -> [ModuleName] -> IO [FilePath]
allSourcesBuildInfo Verbosity
verbosity BuildInfo
exeBi [PPSuffixHandler]
pps []
       FilePath
mainSrc <- Verbosity
-> BuildInfo -> [PPSuffixHandler] -> FilePath -> IO FilePath
findMainExeFile Verbosity
verbosity BuildInfo
exeBi [PPSuffixHandler]
pps FilePath
mainPath
       [FilePath] -> IO [FilePath]
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath
mainSrcFilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
:[FilePath]
biSrcs)

    -- Foreign library sources
  , ([[FilePath]] -> [FilePath]) -> IO [[FilePath]] -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [[FilePath]] -> [FilePath]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
    (IO [[FilePath]] -> IO [FilePath])
-> ((ForeignLib -> IO [FilePath]) -> IO [[FilePath]])
-> (ForeignLib -> IO [FilePath])
-> IO [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ForeignLib -> IO [FilePath]) -> IO [[FilePath]]
forall (f :: * -> *) b.
Applicative f =>
(ForeignLib -> f b) -> f [b]
withAllFLib ((ForeignLib -> IO [FilePath]) -> IO [FilePath])
-> (ForeignLib -> IO [FilePath]) -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ \flib :: ForeignLib
flib@(ForeignLib { foreignLibBuildInfo :: ForeignLib -> BuildInfo
foreignLibBuildInfo = BuildInfo
flibBi }) -> do
       [FilePath]
biSrcs   <- Verbosity
-> BuildInfo -> [PPSuffixHandler] -> [ModuleName] -> IO [FilePath]
allSourcesBuildInfo Verbosity
verbosity BuildInfo
flibBi [PPSuffixHandler]
pps []
       [FilePath]
defFiles <- (FilePath -> NoCallStackIO FilePath) -> [FilePath] -> IO [FilePath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Verbosity
-> BuildInfo -> [PPSuffixHandler] -> FilePath -> IO FilePath
findModDefFile Verbosity
verbosity BuildInfo
flibBi [PPSuffixHandler]
pps)
         (ForeignLib -> [FilePath]
foreignLibModDefFile ForeignLib
flib)
       [FilePath] -> IO [FilePath]
forall (m :: * -> *) a. Monad m => a -> m a
return ([FilePath]
defFiles [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath]
biSrcs)

    -- Test suites sources.
  , ([[FilePath]] -> [FilePath]) -> IO [[FilePath]] -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [[FilePath]] -> [FilePath]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
    (IO [[FilePath]] -> IO [FilePath])
-> ((TestSuite -> IO [FilePath]) -> IO [[FilePath]])
-> (TestSuite -> IO [FilePath])
-> IO [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TestSuite -> IO [FilePath]) -> IO [[FilePath]]
forall (f :: * -> *) b.
Applicative f =>
(TestSuite -> f b) -> f [b]
withAllTest ((TestSuite -> IO [FilePath]) -> IO [FilePath])
-> (TestSuite -> IO [FilePath]) -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ \TestSuite
t -> do
       let bi :: BuildInfo
bi  = TestSuite -> BuildInfo
testBuildInfo TestSuite
t
       case TestSuite -> TestSuiteInterface
testInterface TestSuite
t of
         TestSuiteExeV10 Version
_ FilePath
mainPath -> do
           [FilePath]
biSrcs <- Verbosity
-> BuildInfo -> [PPSuffixHandler] -> [ModuleName] -> IO [FilePath]
allSourcesBuildInfo Verbosity
verbosity BuildInfo
bi [PPSuffixHandler]
pps []
           FilePath
srcMainFile <- Verbosity
-> BuildInfo -> [PPSuffixHandler] -> FilePath -> IO FilePath
findMainExeFile Verbosity
verbosity BuildInfo
bi [PPSuffixHandler]
pps FilePath
mainPath
           [FilePath] -> IO [FilePath]
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath
srcMainFileFilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
:[FilePath]
biSrcs)
         TestSuiteLibV09 Version
_ ModuleName
m ->
           Verbosity
-> BuildInfo -> [PPSuffixHandler] -> [ModuleName] -> IO [FilePath]
allSourcesBuildInfo Verbosity
verbosity BuildInfo
bi [PPSuffixHandler]
pps [ModuleName
m]
         TestSuiteUnsupported TestType
tp ->
           Verbosity -> FilePath -> IO [FilePath]
forall a. Verbosity -> FilePath -> IO a
die' Verbosity
verbosity (FilePath -> IO [FilePath]) -> FilePath -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ FilePath
"Unsupported test suite type: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ TestType -> FilePath
forall a. Show a => a -> FilePath
show TestType
tp

    -- Benchmarks sources.
  , ([[FilePath]] -> [FilePath]) -> IO [[FilePath]] -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [[FilePath]] -> [FilePath]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
    (IO [[FilePath]] -> IO [FilePath])
-> ((Benchmark -> IO [FilePath]) -> IO [[FilePath]])
-> (Benchmark -> IO [FilePath])
-> IO [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Benchmark -> IO [FilePath]) -> IO [[FilePath]]
forall (f :: * -> *) b.
Applicative f =>
(Benchmark -> f b) -> f [b]
withAllBenchmark ((Benchmark -> IO [FilePath]) -> IO [FilePath])
-> (Benchmark -> IO [FilePath]) -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ \Benchmark
bm -> do
       let  bi :: BuildInfo
bi = Benchmark -> BuildInfo
benchmarkBuildInfo Benchmark
bm
       case Benchmark -> BenchmarkInterface
benchmarkInterface Benchmark
bm of
         BenchmarkExeV10 Version
_ FilePath
mainPath -> do
           [FilePath]
biSrcs <- Verbosity
-> BuildInfo -> [PPSuffixHandler] -> [ModuleName] -> IO [FilePath]
allSourcesBuildInfo Verbosity
verbosity BuildInfo
bi [PPSuffixHandler]
pps []
           FilePath
srcMainFile <- Verbosity
-> BuildInfo -> [PPSuffixHandler] -> FilePath -> IO FilePath
findMainExeFile Verbosity
verbosity BuildInfo
bi [PPSuffixHandler]
pps FilePath
mainPath
           [FilePath] -> IO [FilePath]
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath
srcMainFileFilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
:[FilePath]
biSrcs)
         BenchmarkUnsupported BenchmarkType
tp -> Verbosity -> FilePath -> IO [FilePath]
forall a. Verbosity -> FilePath -> IO a
die' Verbosity
verbosity (FilePath -> IO [FilePath]) -> FilePath -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ FilePath
"Unsupported benchmark type: "
                                    FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ BenchmarkType -> FilePath
forall a. Show a => a -> FilePath
show BenchmarkType
tp

    -- Data files.
  , ([[FilePath]] -> [FilePath]) -> IO [[FilePath]] -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [[FilePath]] -> [FilePath]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
    (IO [[FilePath]] -> IO [FilePath])
-> ((FilePath -> IO [FilePath]) -> IO [[FilePath]])
-> (FilePath -> IO [FilePath])
-> IO [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> (FilePath -> IO [FilePath]) -> IO [[FilePath]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for (PackageDescription -> [FilePath]
dataFiles PackageDescription
pkg_descr) ((FilePath -> IO [FilePath]) -> IO [FilePath])
-> (FilePath -> IO [FilePath]) -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ \FilePath
filename ->
        let srcDataDirRaw :: FilePath
srcDataDirRaw = PackageDescription -> FilePath
dataDir PackageDescription
pkg_descr
            srcDataDir :: FilePath
srcDataDir = if FilePath -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
srcDataDirRaw
              then FilePath
"."
              else FilePath
srcDataDirRaw
        in ([FilePath] -> [FilePath]) -> IO [FilePath] -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (FilePath
srcDataDir FilePath -> FilePath -> FilePath
</>)) (IO [FilePath] -> IO [FilePath]) -> IO [FilePath] -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$
             Verbosity -> Version -> FilePath -> FilePath -> IO [FilePath]
matchDirFileGlob Verbosity
verbosity (PackageDescription -> Version
specVersion PackageDescription
pkg_descr) FilePath
srcDataDir FilePath
filename

    -- Extra doc files.
  , ([[FilePath]] -> [FilePath]) -> IO [[FilePath]] -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [[FilePath]] -> [FilePath]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
    (IO [[FilePath]] -> IO [FilePath])
-> ((FilePath -> IO [FilePath]) -> IO [[FilePath]])
-> (FilePath -> IO [FilePath])
-> IO [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> (FilePath -> IO [FilePath]) -> IO [[FilePath]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for (PackageDescription -> [FilePath]
extraDocFiles PackageDescription
pkg_descr) ((FilePath -> IO [FilePath]) -> IO [FilePath])
-> (FilePath -> IO [FilePath]) -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ \ FilePath
filename ->
        Verbosity -> Version -> FilePath -> FilePath -> IO [FilePath]
matchDirFileGlob Verbosity
verbosity (PackageDescription -> Version
specVersion PackageDescription
pkg_descr) FilePath
"." FilePath
filename

    -- License file(s).
  , [FilePath] -> IO [FilePath]
forall (m :: * -> *) a. Monad m => a -> m a
return (PackageDescription -> [FilePath]
licenseFiles PackageDescription
pkg_descr)

    -- Install-include files, without autogen-include files
  , ([[FilePath]] -> [FilePath]) -> IO [[FilePath]] -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [[FilePath]] -> [FilePath]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
    (IO [[FilePath]] -> IO [FilePath])
-> ((Library -> IO [FilePath]) -> IO [[FilePath]])
-> (Library -> IO [FilePath])
-> IO [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Library -> IO [FilePath]) -> IO [[FilePath]]
forall (f :: * -> *) b. Applicative f => (Library -> f b) -> f [b]
withAllLib ((Library -> IO [FilePath]) -> IO [FilePath])
-> (Library -> IO [FilePath]) -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ \ Library
l -> do
       let lbi :: BuildInfo
lbi   = Library -> BuildInfo
libBuildInfo Library
l
           incls :: [FilePath]
incls = (FilePath -> Bool) -> [FilePath] -> [FilePath]
forall a. (a -> Bool) -> [a] -> [a]
filter (FilePath -> [FilePath] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` BuildInfo -> [FilePath]
autogenIncludes BuildInfo
lbi) (BuildInfo -> [FilePath]
installIncludes BuildInfo
lbi)
           relincdirs :: [FilePath]
relincdirs = FilePath
"." FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: (FilePath -> Bool) -> [FilePath] -> [FilePath]
forall a. (a -> Bool) -> [a] -> [a]
filter FilePath -> Bool
isRelative (BuildInfo -> [FilePath]
includeDirs BuildInfo
lbi)
       (FilePath -> NoCallStackIO FilePath) -> [FilePath] -> IO [FilePath]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (((FilePath, FilePath) -> FilePath)
-> IO (FilePath, FilePath) -> NoCallStackIO FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (FilePath, FilePath) -> FilePath
forall a b. (a, b) -> b
snd (IO (FilePath, FilePath) -> NoCallStackIO FilePath)
-> (FilePath -> IO (FilePath, FilePath))
-> FilePath
-> NoCallStackIO FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Verbosity -> [FilePath] -> FilePath -> IO (FilePath, FilePath)
findIncludeFile Verbosity
verbosity [FilePath]
relincdirs) [FilePath]
incls

    -- Setup script, if it exists.
  , (Maybe FilePath -> [FilePath])
-> IO (Maybe FilePath) -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([FilePath]
-> (FilePath -> [FilePath]) -> Maybe FilePath -> [FilePath]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\FilePath
f -> [FilePath
f])) (IO (Maybe FilePath) -> IO [FilePath])
-> IO (Maybe FilePath) -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ FilePath -> IO (Maybe FilePath)
findSetupFile FilePath
""

    -- The .cabal file itself.
  , (FilePath -> [FilePath]) -> NoCallStackIO FilePath -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\FilePath
d -> [FilePath
d]) (Verbosity -> IO FilePath
defaultPackageDesc Verbosity
verbosity)

  ]
  where
    -- We have to deal with all libs and executables, so we have local
    -- versions of these functions that ignore the 'buildable' attribute:
    withAllLib :: (Library -> f b) -> f [b]
withAllLib       Library -> f b
action = (Library -> f b) -> [Library] -> f [b]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Library -> f b
action (PackageDescription -> [Library]
allLibraries PackageDescription
pkg_descr)
    withAllFLib :: (ForeignLib -> f b) -> f [b]
withAllFLib      ForeignLib -> f b
action = (ForeignLib -> f b) -> [ForeignLib] -> f [b]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ForeignLib -> f b
action (PackageDescription -> [ForeignLib]
foreignLibs PackageDescription
pkg_descr)
    withAllExe :: (Executable -> f b) -> f [b]
withAllExe       Executable -> f b
action = (Executable -> f b) -> [Executable] -> f [b]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Executable -> f b
action (PackageDescription -> [Executable]
executables PackageDescription
pkg_descr)
    withAllTest :: (TestSuite -> f b) -> f [b]
withAllTest      TestSuite -> f b
action = (TestSuite -> f b) -> [TestSuite] -> f [b]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse TestSuite -> f b
action (PackageDescription -> [TestSuite]
testSuites PackageDescription
pkg_descr)
    withAllBenchmark :: (Benchmark -> f b) -> f [b]
withAllBenchmark Benchmark -> f b
action = (Benchmark -> f b) -> [Benchmark] -> f [b]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Benchmark -> f b
action (PackageDescription -> [Benchmark]
benchmarks PackageDescription
pkg_descr)


-- |Prepare a directory tree of source files.
prepareTree :: Verbosity          -- ^verbosity
            -> PackageDescription -- ^info from the cabal file
            -> Maybe LocalBuildInfo
            -> FilePath           -- ^source tree to populate
            -> [PPSuffixHandler]  -- ^extra preprocessors (includes suffixes)
            -> IO ()
prepareTree :: Verbosity
-> PackageDescription
-> Maybe LocalBuildInfo
-> FilePath
-> [PPSuffixHandler]
-> IO ()
prepareTree Verbosity
verbosity PackageDescription
pkg_descr0 Maybe LocalBuildInfo
mb_lbi FilePath
targetDir [PPSuffixHandler]
pps = do
  -- If the package was configured then we can run platform-independent
  -- pre-processors and include those generated files.
  case Maybe LocalBuildInfo
mb_lbi of
    Just LocalBuildInfo
lbi | Bool -> Bool
not ([PPSuffixHandler] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [PPSuffixHandler]
pps) -> do
      let lbi' :: LocalBuildInfo
lbi' = LocalBuildInfo
lbi{ buildDir :: FilePath
buildDir = FilePath
targetDir FilePath -> FilePath -> FilePath
</> LocalBuildInfo -> FilePath
buildDir LocalBuildInfo
lbi }
      PackageDescription
-> LocalBuildInfo
-> (Component -> ComponentLocalBuildInfo -> IO ())
-> IO ()
withAllComponentsInBuildOrder PackageDescription
pkg_descr LocalBuildInfo
lbi' ((Component -> ComponentLocalBuildInfo -> IO ()) -> IO ())
-> (Component -> ComponentLocalBuildInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Component
c ComponentLocalBuildInfo
clbi ->
        PackageDescription
-> Component
-> LocalBuildInfo
-> ComponentLocalBuildInfo
-> Bool
-> Verbosity
-> [PPSuffixHandler]
-> IO ()
preprocessComponent PackageDescription
pkg_descr Component
c LocalBuildInfo
lbi' ComponentLocalBuildInfo
clbi Bool
True Verbosity
verbosity [PPSuffixHandler]
pps
    Maybe LocalBuildInfo
_ -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

  ([FilePath]
ordinary, [FilePath]
mExecutable)  <- Verbosity
-> PackageDescription
-> [PPSuffixHandler]
-> IO ([FilePath], [FilePath])
listPackageSources Verbosity
verbosity PackageDescription
pkg_descr0 [PPSuffixHandler]
pps
  Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()
installOrdinaryFiles        Verbosity
verbosity FilePath
targetDir ([FilePath] -> [FilePath] -> [(FilePath, FilePath)]
forall a b. [a] -> [b] -> [(a, b)]
zip (FilePath -> [FilePath]
forall a. a -> [a]
repeat []) [FilePath]
ordinary)
  Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()
installMaybeExecutableFiles Verbosity
verbosity FilePath
targetDir ([FilePath] -> [FilePath] -> [(FilePath, FilePath)]
forall a b. [a] -> [b] -> [(a, b)]
zip (FilePath -> [FilePath]
forall a. a -> [a]
repeat []) [FilePath]
mExecutable)
  FilePath -> IO ()
maybeCreateDefaultSetupScript FilePath
targetDir

  where
    pkg_descr :: PackageDescription
pkg_descr = PackageDescription -> PackageDescription
filterAutogenModules PackageDescription
pkg_descr0

-- | Find the setup script file, if it exists.
findSetupFile :: FilePath -> NoCallStackIO (Maybe FilePath)
findSetupFile :: FilePath -> IO (Maybe FilePath)
findSetupFile FilePath
targetDir = do
  Bool
hsExists  <- FilePath -> IO Bool
doesFileExist FilePath
setupHs
  Bool
lhsExists <- FilePath -> IO Bool
doesFileExist FilePath
setupLhs
  if Bool
hsExists
    then Maybe FilePath -> IO (Maybe FilePath)
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
setupHs)
    else if Bool
lhsExists
         then Maybe FilePath -> IO (Maybe FilePath)
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
setupLhs)
         else Maybe FilePath -> IO (Maybe FilePath)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FilePath
forall a. Maybe a
Nothing
    where
      setupHs :: FilePath
setupHs  = FilePath
targetDir FilePath -> FilePath -> FilePath
</> FilePath
"Setup.hs"
      setupLhs :: FilePath
setupLhs = FilePath
targetDir FilePath -> FilePath -> FilePath
</> FilePath
"Setup.lhs"

-- | Create a default setup script in the target directory, if it doesn't exist.
maybeCreateDefaultSetupScript :: FilePath -> NoCallStackIO ()
maybeCreateDefaultSetupScript :: FilePath -> IO ()
maybeCreateDefaultSetupScript FilePath
targetDir = do
  Maybe FilePath
mSetupFile <- FilePath -> IO (Maybe FilePath)
findSetupFile FilePath
targetDir
  case Maybe FilePath
mSetupFile of
    Just FilePath
_setupFile -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
    Maybe FilePath
Nothing         -> do
      FilePath -> FilePath -> IO ()
writeUTF8File (FilePath
targetDir FilePath -> FilePath -> FilePath
</> FilePath
"Setup.hs") (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
unlines [
        FilePath
"import Distribution.Simple",
        FilePath
"main = defaultMain"]

-- | Find the main executable file.
findMainExeFile
  :: Verbosity -> BuildInfo -> [PPSuffixHandler] -> FilePath -> IO FilePath
findMainExeFile :: Verbosity
-> BuildInfo -> [PPSuffixHandler] -> FilePath -> IO FilePath
findMainExeFile Verbosity
verbosity BuildInfo
exeBi [PPSuffixHandler]
pps FilePath
mainPath = do
  Maybe FilePath
ppFile <- [FilePath] -> [FilePath] -> FilePath -> IO (Maybe FilePath)
findFileWithExtension ([PPSuffixHandler] -> [FilePath]
ppSuffixes [PPSuffixHandler]
pps) (BuildInfo -> [FilePath]
hsSourceDirs BuildInfo
exeBi)
            (FilePath -> FilePath
dropExtension FilePath
mainPath)
  case Maybe FilePath
ppFile of
    Maybe FilePath
Nothing -> Verbosity -> [FilePath] -> FilePath -> IO FilePath
findFileEx Verbosity
verbosity (BuildInfo -> [FilePath]
hsSourceDirs BuildInfo
exeBi) FilePath
mainPath
    Just FilePath
pp -> FilePath -> NoCallStackIO FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
pp

-- | Find a module definition file
--
-- TODO: I don't know if this is right
findModDefFile
  :: Verbosity -> BuildInfo -> [PPSuffixHandler] -> FilePath -> IO FilePath
findModDefFile :: Verbosity
-> BuildInfo -> [PPSuffixHandler] -> FilePath -> IO FilePath
findModDefFile Verbosity
verbosity BuildInfo
flibBi [PPSuffixHandler]
_pps FilePath
modDefPath =
    Verbosity -> [FilePath] -> FilePath -> IO FilePath
findFileEx Verbosity
verbosity (FilePath
"."FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
:BuildInfo -> [FilePath]
hsSourceDirs BuildInfo
flibBi) FilePath
modDefPath

-- | Given a list of include paths, try to find the include file named
-- @f@. Return the name of the file and the full path, or exit with error if
-- there's no such file.
findIncludeFile :: Verbosity -> [FilePath] -> String -> IO (String, FilePath)
findIncludeFile :: Verbosity -> [FilePath] -> FilePath -> IO (FilePath, FilePath)
findIncludeFile Verbosity
verbosity [] FilePath
f = Verbosity -> FilePath -> IO (FilePath, FilePath)
forall a. Verbosity -> FilePath -> IO a
die' Verbosity
verbosity (FilePath
"can't find include file " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
f)
findIncludeFile Verbosity
verbosity (FilePath
d:[FilePath]
ds) FilePath
f = do
  let path :: FilePath
path = (FilePath
d FilePath -> FilePath -> FilePath
</> FilePath
f)
  Bool
b <- FilePath -> IO Bool
doesFileExist FilePath
path
  if Bool
b then (FilePath, FilePath) -> IO (FilePath, FilePath)
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath
f,FilePath
path) else Verbosity -> [FilePath] -> FilePath -> IO (FilePath, FilePath)
findIncludeFile Verbosity
verbosity [FilePath]
ds FilePath
f

-- | Remove the auto-generated modules (like 'Paths_*') from 'exposed-modules' 
-- and 'other-modules'.
filterAutogenModules :: PackageDescription -> PackageDescription
filterAutogenModules :: PackageDescription -> PackageDescription
filterAutogenModules PackageDescription
pkg_descr0 = (Library -> Library) -> PackageDescription -> PackageDescription
mapLib Library -> Library
filterAutogenModuleLib (PackageDescription -> PackageDescription)
-> PackageDescription -> PackageDescription
forall a b. (a -> b) -> a -> b
$
                                 (BuildInfo -> BuildInfo)
-> PackageDescription -> PackageDescription
mapAllBuildInfo BuildInfo -> BuildInfo
filterAutogenModuleBI PackageDescription
pkg_descr0
  where
    mapLib :: (Library -> Library) -> PackageDescription -> PackageDescription
mapLib Library -> Library
f PackageDescription
pkg = PackageDescription
pkg { 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
f (PackageDescription -> Maybe Library
library PackageDescription
pkg)
                       , subLibraries :: [Library]
subLibraries = (Library -> Library) -> [Library] -> [Library]
forall a b. (a -> b) -> [a] -> [b]
map Library -> Library
f (PackageDescription -> [Library]
subLibraries PackageDescription
pkg) }
    filterAutogenModuleLib :: Library -> Library
filterAutogenModuleLib Library
lib = Library
lib {
      exposedModules :: [ModuleName]
exposedModules = (ModuleName -> Bool) -> [ModuleName] -> [ModuleName]
forall a. (a -> Bool) -> [a] -> [a]
filter (BuildInfo -> ModuleName -> Bool
filterFunction (Library -> BuildInfo
libBuildInfo Library
lib)) (Library -> [ModuleName]
exposedModules Library
lib)
    }
    filterAutogenModuleBI :: BuildInfo -> BuildInfo
filterAutogenModuleBI BuildInfo
bi = BuildInfo
bi {
      otherModules :: [ModuleName]
otherModules   = (ModuleName -> Bool) -> [ModuleName] -> [ModuleName]
forall a. (a -> Bool) -> [a] -> [a]
filter (BuildInfo -> ModuleName -> Bool
filterFunction BuildInfo
bi) (BuildInfo -> [ModuleName]
otherModules BuildInfo
bi)
    }
    pathsModule :: ModuleName
pathsModule = PackageDescription -> ModuleName
autogenPathsModuleName PackageDescription
pkg_descr0
    filterFunction :: BuildInfo -> ModuleName -> Bool
filterFunction BuildInfo
bi = \ModuleName
mn ->
                                   ModuleName
mn ModuleName -> ModuleName -> Bool
forall a. Eq a => a -> a -> Bool
/= ModuleName
pathsModule
                                Bool -> Bool -> Bool
&& Bool -> Bool
not (ModuleName
mn ModuleName -> [ModuleName] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` BuildInfo -> [ModuleName]
autogenModules BuildInfo
bi)

-- | Prepare a directory tree of source files for a snapshot version.
-- It is expected that the appropriate snapshot version has already been set
-- in the package description, eg using 'snapshotPackage' or 'snapshotVersion'.
--
prepareSnapshotTree :: Verbosity          -- ^verbosity
                    -> PackageDescription -- ^info from the cabal file
                    -> Maybe LocalBuildInfo
                    -> FilePath           -- ^source tree to populate
                    -> [PPSuffixHandler]  -- ^extra preprocessors (includes
                                          -- suffixes)
                    -> IO ()
prepareSnapshotTree :: Verbosity
-> PackageDescription
-> Maybe LocalBuildInfo
-> FilePath
-> [PPSuffixHandler]
-> IO ()
prepareSnapshotTree Verbosity
verbosity PackageDescription
pkg Maybe LocalBuildInfo
mb_lbi FilePath
targetDir [PPSuffixHandler]
pps = do
  Verbosity
-> PackageDescription
-> Maybe LocalBuildInfo
-> FilePath
-> [PPSuffixHandler]
-> IO ()
prepareTree Verbosity
verbosity PackageDescription
pkg Maybe LocalBuildInfo
mb_lbi FilePath
targetDir [PPSuffixHandler]
pps
  Verbosity -> PackageDescription -> FilePath -> IO ()
overwriteSnapshotPackageDesc Verbosity
verbosity PackageDescription
pkg FilePath
targetDir

overwriteSnapshotPackageDesc :: Verbosity          -- ^verbosity
                             -> PackageDescription -- ^info from the cabal file
                             -> FilePath           -- ^source tree
                             -> IO ()
overwriteSnapshotPackageDesc :: Verbosity -> PackageDescription -> FilePath -> IO ()
overwriteSnapshotPackageDesc Verbosity
verbosity PackageDescription
pkg FilePath
targetDir = do
    -- We could just writePackageDescription targetDescFile pkg_descr,
    -- but that would lose comments and formatting.
    FilePath
descFile <- Verbosity -> IO FilePath
defaultPackageDesc Verbosity
verbosity
    FilePath -> (FilePath -> IO ()) -> IO ()
forall a. FilePath -> (FilePath -> IO a) -> IO a
withUTF8FileContents FilePath
descFile ((FilePath -> IO ()) -> IO ()) -> (FilePath -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$
      FilePath -> FilePath -> IO ()
writeUTF8File (FilePath
targetDir FilePath -> FilePath -> FilePath
</> FilePath
descFile)
        (FilePath -> IO ()) -> (FilePath -> FilePath) -> FilePath -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> FilePath
unlines ([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 (Version -> FilePath -> FilePath
replaceVersion (PackageDescription -> Version
forall pkg. Package pkg => pkg -> Version
packageVersion PackageDescription
pkg)) ([FilePath] -> [FilePath])
-> (FilePath -> [FilePath]) -> FilePath -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> [FilePath]
lines

  where
    replaceVersion :: Version -> String -> String
    replaceVersion :: Version -> FilePath -> FilePath
replaceVersion Version
version FilePath
line
      | FilePath
"version:" FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` (Char -> Char) -> FilePath -> FilePath
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower FilePath
line
                  = FilePath
"version: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Version -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow Version
version
      | Bool
otherwise = FilePath
line

-- | Modifies a 'PackageDescription' by appending a snapshot number
-- corresponding to the given date.
--
snapshotPackage :: UTCTime -> PackageDescription -> PackageDescription
snapshotPackage :: UTCTime -> PackageDescription -> PackageDescription
snapshotPackage UTCTime
date PackageDescription
pkg =
  PackageDescription
pkg {
    package :: PackageIdentifier
package = PackageIdentifier
pkgid { pkgVersion :: Version
pkgVersion = UTCTime -> Version -> Version
snapshotVersion UTCTime
date (PackageIdentifier -> Version
pkgVersion PackageIdentifier
pkgid) }
  }
  where pkgid :: PackageIdentifier
pkgid = PackageDescription -> PackageIdentifier
forall pkg. Package pkg => pkg -> PackageIdentifier
packageId PackageDescription
pkg

-- | Modifies a 'Version' by appending a snapshot number corresponding
-- to the given date.
--
snapshotVersion :: UTCTime -> Version -> Version
snapshotVersion :: UTCTime -> Version -> Version
snapshotVersion UTCTime
date = ([Int] -> [Int]) -> Version -> Version
alterVersion ([Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ [UTCTime -> Int
dateToSnapshotNumber UTCTime
date])

-- | Given a date produce a corresponding integer representation.
-- For example given a date @18/03/2008@ produce the number @20080318@.
--
dateToSnapshotNumber :: UTCTime -> Int
dateToSnapshotNumber :: UTCTime -> Int
dateToSnapshotNumber UTCTime
date = case Day -> (Integer, Int, Int)
toGregorian (UTCTime -> Day
utctDay UTCTime
date) of
                            (Integer
year, Int
month, Int
day) ->
                                Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
year Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
10000
                              Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
month             Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
100
                              Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
day

-- | Callback type for use by sdistWith.
type CreateArchiveFun = Verbosity               -- ^verbosity
                        -> PackageDescription   -- ^info from cabal file
                        -> Maybe LocalBuildInfo -- ^info from configure
                        -> FilePath             -- ^source tree to archive
                        -> FilePath             -- ^name of archive to create
                        -> IO FilePath

-- | Create an archive from a tree of source files, and clean up the tree.
createArchive :: CreateArchiveFun
createArchive :: CreateArchiveFun
createArchive Verbosity
verbosity PackageDescription
pkg_descr Maybe LocalBuildInfo
mb_lbi FilePath
tmpDir FilePath
targetPref = do
  let tarBallFilePath :: FilePath
tarBallFilePath = FilePath
targetPref FilePath -> FilePath -> FilePath
</> PackageDescription -> FilePath
tarBallName PackageDescription
pkg_descr FilePath -> FilePath -> FilePath
<.> FilePath
"tar.gz"

  (ConfiguredProgram
tarProg, ProgramDb
_) <- Verbosity
-> Program -> ProgramDb -> IO (ConfiguredProgram, ProgramDb)
requireProgram Verbosity
verbosity Program
tarProgram
                    (ProgramDb
-> (LocalBuildInfo -> ProgramDb)
-> Maybe LocalBuildInfo
-> ProgramDb
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ProgramDb
defaultProgramDb LocalBuildInfo -> ProgramDb
withPrograms Maybe LocalBuildInfo
mb_lbi)
  let formatOptSupported :: Bool
formatOptSupported = Bool -> (FilePath -> Bool) -> Maybe FilePath -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"YES") (Maybe FilePath -> Bool) -> Maybe FilePath -> Bool
forall a b. (a -> b) -> a -> b
$
                           FilePath -> Map FilePath FilePath -> Maybe FilePath
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup FilePath
"Supports --format"
                           (ConfiguredProgram -> Map FilePath FilePath
programProperties ConfiguredProgram
tarProg)
  Verbosity -> ConfiguredProgram -> [FilePath] -> IO ()
runProgram Verbosity
verbosity ConfiguredProgram
tarProg ([FilePath] -> IO ()) -> [FilePath] -> IO ()
forall a b. (a -> b) -> a -> b
$
    -- Hmm: I could well be skating on thinner ice here by using the -C option
    -- (=> seems to be supported at least by GNU and *BSD tar) [The
    -- prev. solution used pipes and sub-command sequences to set up the paths
    -- correctly, which is problematic in a Windows setting.]
    [FilePath
"-czf", FilePath
tarBallFilePath, FilePath
"-C", FilePath
tmpDir]
    [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ (if Bool
formatOptSupported then [FilePath
"--format", FilePath
"ustar"] else [])
    [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [PackageDescription -> FilePath
tarBallName PackageDescription
pkg_descr]
  FilePath -> NoCallStackIO FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
tarBallFilePath

-- | Given a buildinfo, return the names of all source files.
allSourcesBuildInfo :: Verbosity
                       -> BuildInfo
                       -> [PPSuffixHandler] -- ^ Extra preprocessors
                       -> [ModuleName]      -- ^ Exposed modules
                       -> IO [FilePath]
allSourcesBuildInfo :: Verbosity
-> BuildInfo -> [PPSuffixHandler] -> [ModuleName] -> IO [FilePath]
allSourcesBuildInfo Verbosity
verbosity BuildInfo
bi [PPSuffixHandler]
pps [ModuleName]
modules = do
  let searchDirs :: [FilePath]
searchDirs = BuildInfo -> [FilePath]
hsSourceDirs BuildInfo
bi
  [FilePath]
sources <- ([[FilePath]] -> [FilePath]) -> IO [[FilePath]] -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [[FilePath]] -> [FilePath]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (IO [[FilePath]] -> IO [FilePath])
-> IO [[FilePath]] -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ [IO [FilePath]] -> IO [[FilePath]]
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA ([IO [FilePath]] -> IO [[FilePath]])
-> [IO [FilePath]] -> IO [[FilePath]]
forall a b. (a -> b) -> a -> b
$
    [ let file :: FilePath
file = ModuleName -> FilePath
ModuleName.toFilePath ModuleName
module_
      -- NB: *Not* findFileWithExtension, because the same source
      -- file may show up in multiple paths due to a conditional;
      -- we need to package all of them.  See #367.
      in [FilePath] -> [FilePath] -> FilePath -> IO [FilePath]
findAllFilesWithExtension [FilePath]
suffixes [FilePath]
searchDirs FilePath
file
         IO [FilePath] -> ([FilePath] -> IO [FilePath]) -> IO [FilePath]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= IO [FilePath]
-> ([FilePath] -> IO [FilePath]) -> [FilePath] -> IO [FilePath]
forall p a. p -> ([a] -> p) -> [a] -> p
nonEmpty (ModuleName -> IO [FilePath]
forall a a. Pretty a => a -> IO a
notFound ModuleName
module_) [FilePath] -> IO [FilePath]
forall (m :: * -> *) a. Monad m => a -> m a
return
    | ModuleName
module_ <- [ModuleName]
modules [ModuleName] -> [ModuleName] -> [ModuleName]
forall a. [a] -> [a] -> [a]
++ BuildInfo -> [ModuleName]
otherModules BuildInfo
bi ]
  [Maybe FilePath]
bootFiles <- [IO (Maybe FilePath)] -> IO [Maybe FilePath]
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA
    [ let file :: FilePath
file = ModuleName -> FilePath
ModuleName.toFilePath ModuleName
module_
          fileExts :: [FilePath]
fileExts = [FilePath
"hs-boot", FilePath
"lhs-boot"]
      in [FilePath] -> [FilePath] -> FilePath -> IO (Maybe FilePath)
findFileWithExtension [FilePath]
fileExts (BuildInfo -> [FilePath]
hsSourceDirs BuildInfo
bi) FilePath
file
    | ModuleName
module_ <- [ModuleName]
modules [ModuleName] -> [ModuleName] -> [ModuleName]
forall a. [a] -> [a] -> [a]
++ BuildInfo -> [ModuleName]
otherModules BuildInfo
bi ]

  [FilePath] -> IO [FilePath]
forall (m :: * -> *) a. Monad m => a -> m a
return ([FilePath] -> IO [FilePath]) -> [FilePath] -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ [FilePath]
sources [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [Maybe FilePath] -> [FilePath]
forall a. [Maybe a] -> [a]
catMaybes [Maybe FilePath]
bootFiles [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ BuildInfo -> [FilePath]
cSources BuildInfo
bi [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ BuildInfo -> [FilePath]
cxxSources BuildInfo
bi [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++
           BuildInfo -> [FilePath]
cmmSources BuildInfo
bi [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ BuildInfo -> [FilePath]
asmSources BuildInfo
bi [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ BuildInfo -> [FilePath]
jsSources BuildInfo
bi

  where
    nonEmpty :: p -> ([a] -> p) -> [a] -> p
nonEmpty p
x [a] -> p
_ [] = p
x
    nonEmpty p
_ [a] -> p
f [a]
xs = [a] -> p
f [a]
xs
    suffixes :: [FilePath]
suffixes = [PPSuffixHandler] -> [FilePath]
ppSuffixes [PPSuffixHandler]
pps [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath
"hs", FilePath
"lhs", FilePath
"hsig", FilePath
"lhsig"]
    notFound :: a -> IO a
notFound a
m = Verbosity -> FilePath -> IO a
forall a. Verbosity -> FilePath -> IO a
die' Verbosity
verbosity (FilePath -> IO a) -> FilePath -> IO a
forall a b. (a -> b) -> a -> b
$ FilePath
"Error: Could not find module: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ a -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow a
m
                 FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" with any suffix: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ [FilePath] -> FilePath
forall a. Show a => a -> FilePath
show [FilePath]
suffixes FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
". If the module "
                 FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"is autogenerated it should be added to 'autogen-modules'."


-- | Note: must be called with the CWD set to the directory containing
-- the '.cabal' file.
printPackageProblems :: Verbosity -> PackageDescription -> IO ()
printPackageProblems :: Verbosity -> PackageDescription -> IO ()
printPackageProblems Verbosity
verbosity PackageDescription
pkg_descr = do
  [PackageCheck]
ioChecks      <- Verbosity
-> PackageDescription -> FilePath -> NoCallStackIO [PackageCheck]
checkPackageFiles Verbosity
verbosity PackageDescription
pkg_descr FilePath
"."
  let pureChecks :: [PackageCheck]
pureChecks = PackageDescription -> [PackageCheck]
checkConfiguredPackage PackageDescription
pkg_descr
      isDistError :: PackageCheck -> Bool
isDistError (PackageDistSuspicious     FilePath
_) = Bool
False
      isDistError (PackageDistSuspiciousWarn FilePath
_) = Bool
False
      isDistError PackageCheck
_                             = Bool
True
      ([PackageCheck]
errors, [PackageCheck]
warnings) = (PackageCheck -> Bool)
-> [PackageCheck] -> ([PackageCheck], [PackageCheck])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition PackageCheck -> Bool
isDistError ([PackageCheck]
pureChecks [PackageCheck] -> [PackageCheck] -> [PackageCheck]
forall a. [a] -> [a] -> [a]
++ [PackageCheck]
ioChecks)
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([PackageCheck] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [PackageCheck]
errors) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
      Verbosity -> FilePath -> IO ()
notice Verbosity
verbosity (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"Distribution quality errors:\n"
                      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ [FilePath] -> FilePath
unlines ((PackageCheck -> FilePath) -> [PackageCheck] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map PackageCheck -> FilePath
explanation [PackageCheck]
errors)
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([PackageCheck] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [PackageCheck]
warnings) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
      Verbosity -> FilePath -> IO ()
notice Verbosity
verbosity (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"Distribution quality warnings:\n"
                      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ [FilePath] -> FilePath
unlines ((PackageCheck -> FilePath) -> [PackageCheck] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map PackageCheck -> FilePath
explanation [PackageCheck]
warnings)
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([PackageCheck] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [PackageCheck]
errors) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
      Verbosity -> FilePath -> IO ()
notice Verbosity
verbosity
        FilePath
"Note: the public hackage server would reject this package."

------------------------------------------------------------

-- | The name of the tarball without extension
--
tarBallName :: PackageDescription -> String
tarBallName :: PackageDescription -> FilePath
tarBallName = PackageIdentifier -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow (PackageIdentifier -> FilePath)
-> (PackageDescription -> PackageIdentifier)
-> PackageDescription
-> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageDescription -> PackageIdentifier
forall pkg. Package pkg => pkg -> PackageIdentifier
packageId

mapAllBuildInfo :: (BuildInfo -> BuildInfo)
                -> (PackageDescription -> PackageDescription)
mapAllBuildInfo :: (BuildInfo -> BuildInfo)
-> PackageDescription -> PackageDescription
mapAllBuildInfo BuildInfo -> BuildInfo
f PackageDescription
pkg = PackageDescription
pkg {
    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
mapLibBi (PackageDescription -> Maybe Library
library PackageDescription
pkg),
    subLibraries :: [Library]
subLibraries = (Library -> Library) -> [Library] -> [Library]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Library -> Library
mapLibBi (PackageDescription -> [Library]
subLibraries PackageDescription
pkg),
    foreignLibs :: [ForeignLib]
foreignLibs = (ForeignLib -> ForeignLib) -> [ForeignLib] -> [ForeignLib]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ForeignLib -> ForeignLib
mapFLibBi (PackageDescription -> [ForeignLib]
foreignLibs PackageDescription
pkg),
    executables :: [Executable]
executables = (Executable -> Executable) -> [Executable] -> [Executable]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Executable -> Executable
mapExeBi (PackageDescription -> [Executable]
executables PackageDescription
pkg),
    testSuites :: [TestSuite]
testSuites  = (TestSuite -> TestSuite) -> [TestSuite] -> [TestSuite]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TestSuite -> TestSuite
mapTestBi (PackageDescription -> [TestSuite]
testSuites PackageDescription
pkg),
    benchmarks :: [Benchmark]
benchmarks  = (Benchmark -> Benchmark) -> [Benchmark] -> [Benchmark]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Benchmark -> Benchmark
mapBenchBi (PackageDescription -> [Benchmark]
benchmarks PackageDescription
pkg)
  }
  where
    mapLibBi :: Library -> Library
mapLibBi   Library
lib  = Library
lib  { libBuildInfo :: BuildInfo
libBuildInfo        = BuildInfo -> BuildInfo
f (Library -> BuildInfo
libBuildInfo Library
lib) }
    mapFLibBi :: ForeignLib -> ForeignLib
mapFLibBi  ForeignLib
flib = ForeignLib
flib { foreignLibBuildInfo :: BuildInfo
foreignLibBuildInfo = BuildInfo -> BuildInfo
f (ForeignLib -> BuildInfo
foreignLibBuildInfo ForeignLib
flib) }
    mapExeBi :: Executable -> Executable
mapExeBi   Executable
exe  = Executable
exe  { buildInfo :: BuildInfo
buildInfo           = BuildInfo -> BuildInfo
f (Executable -> BuildInfo
buildInfo Executable
exe) }
    mapTestBi :: TestSuite -> TestSuite
mapTestBi  TestSuite
tst  = TestSuite
tst  { testBuildInfo :: BuildInfo
testBuildInfo       = BuildInfo -> BuildInfo
f (TestSuite -> BuildInfo
testBuildInfo TestSuite
tst) }
    mapBenchBi :: Benchmark -> Benchmark
mapBenchBi Benchmark
bm   = Benchmark
bm   { benchmarkBuildInfo :: BuildInfo
benchmarkBuildInfo  = BuildInfo -> BuildInfo
f (Benchmark -> BuildInfo
benchmarkBuildInfo Benchmark
bm) }