PageRenderTime 78ms CodeModel.GetById 17ms RepoModel.GetById 4ms app.codeStats 0ms

/Cabal/Distribution/Simple/SrcDist.hs

https://gitlab.com/kranium/cabal
Haskell | 441 lines | 302 code | 49 blank | 90 comment | 6 complexity | 6dd8d89c3e49f13c91af5361c13165f2 MD5 | raw file
  1. -----------------------------------------------------------------------------
  2. -- |
  3. -- Module : Distribution.Simple.SrcDist
  4. -- Copyright : Simon Marlow 2004
  5. --
  6. -- Maintainer : cabal-devel@haskell.org
  7. -- Portability : portable
  8. --
  9. -- This handles the @sdist@ command. The module exports an 'sdist' action but
  10. -- also some of the phases that make it up so that other tools can use just the
  11. -- bits they need. In particular the preparation of the tree of files to go
  12. -- into the source tarball is separated from actually building the source
  13. -- tarball.
  14. --
  15. -- The 'createArchive' action uses the external @tar@ program and assumes that
  16. -- it accepts the @-z@ flag. Neither of these assumptions are valid on Windows.
  17. -- The 'sdist' action now also does some distribution QA checks.
  18. {- Copyright (c) 2003-2004, Simon Marlow
  19. All rights reserved.
  20. Redistribution and use in source and binary forms, with or without
  21. modification, are permitted provided that the following conditions are
  22. met:
  23. * Redistributions of source code must retain the above copyright
  24. notice, this list of conditions and the following disclaimer.
  25. * Redistributions in binary form must reproduce the above
  26. copyright notice, this list of conditions and the following
  27. disclaimer in the documentation and/or other materials provided
  28. with the distribution.
  29. * Neither the name of Isaac Jones nor the names of other
  30. contributors may be used to endorse or promote products derived
  31. from this software without specific prior written permission.
  32. THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
  33. "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
  34. LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
  35. A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
  36. OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
  37. SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
  38. LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
  39. DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
  40. THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
  41. (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
  42. OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -}
  43. -- NOTE: FIX: we don't have a great way of testing this module, since
  44. -- we can't easily look inside a tarball once its created.
  45. module Distribution.Simple.SrcDist (
  46. -- * The top level action
  47. sdist,
  48. -- ** Parts of 'sdist'
  49. printPackageProblems,
  50. prepareTree,
  51. createArchive,
  52. -- ** Snaphots
  53. prepareSnapshotTree,
  54. snapshotPackage,
  55. snapshotVersion,
  56. dateToSnapshotNumber,
  57. ) where
  58. import Distribution.PackageDescription
  59. ( PackageDescription(..), BuildInfo(..), Executable(..), Library(..)
  60. , TestSuite(..), TestSuiteInterface(..), Benchmark(..)
  61. , BenchmarkInterface(..) )
  62. import Distribution.PackageDescription.Check
  63. ( PackageCheck(..), checkConfiguredPackage, checkPackageFiles )
  64. import Distribution.Package
  65. ( PackageIdentifier(pkgVersion), Package(..), packageVersion )
  66. import Distribution.ModuleName (ModuleName)
  67. import qualified Distribution.ModuleName as ModuleName
  68. import Distribution.Version
  69. ( Version(versionBranch) )
  70. import Distribution.Simple.Utils
  71. ( createDirectoryIfMissingVerbose, withUTF8FileContents, writeUTF8File
  72. , installOrdinaryFile, installOrdinaryFiles, setFileExecutable
  73. , findFile, findFileWithExtension, matchFileGlob
  74. , withTempDirectory, defaultPackageDesc
  75. , die, warn, notice, setupMessage )
  76. import Distribution.Simple.Setup (SDistFlags(..), fromFlag, flagToMaybe)
  77. import Distribution.Simple.PreProcess (PPSuffixHandler, ppSuffixes, preprocessComponent)
  78. import Distribution.Simple.LocalBuildInfo ( LocalBuildInfo(..), withComponentsLBI )
  79. import Distribution.Simple.BuildPaths ( autogenModuleName )
  80. import Distribution.Simple.Program ( defaultProgramConfiguration, requireProgram,
  81. rawSystemProgram, tarProgram )
  82. import Distribution.Text
  83. ( display )
  84. import Control.Monad(when, unless)
  85. import Data.Char (toLower)
  86. import Data.List (partition, isPrefixOf)
  87. import Data.Maybe (isNothing, catMaybes)
  88. import System.Time (getClockTime, toCalendarTime, CalendarTime(..))
  89. import System.Directory
  90. ( doesFileExist, Permissions(executable), getPermissions )
  91. import Distribution.Verbosity (Verbosity)
  92. import System.FilePath
  93. ( (</>), (<.>), takeDirectory, dropExtension, isAbsolute )
  94. -- |Create a source distribution.
  95. sdist :: PackageDescription -- ^information from the tarball
  96. -> Maybe LocalBuildInfo -- ^Information from configure
  97. -> SDistFlags -- ^verbosity & snapshot
  98. -> (FilePath -> FilePath) -- ^build prefix (temp dir)
  99. -> [PPSuffixHandler] -- ^ extra preprocessors (includes suffixes)
  100. -> IO ()
  101. sdist pkg mb_lbi flags mkTmpDir pps = do
  102. -- do some QA
  103. printPackageProblems verbosity pkg
  104. when (isNothing mb_lbi) $
  105. warn verbosity "Cannot run preprocessors. Run 'configure' command first."
  106. date <- toCalendarTime =<< getClockTime
  107. let pkg' | snapshot = snapshotPackage date pkg
  108. | otherwise = pkg
  109. case flagToMaybe (sDistDirectory flags) of
  110. Just targetDir -> do
  111. generateSourceDir targetDir pkg'
  112. notice verbosity $ "Source directory created: " ++ targetDir
  113. Nothing -> do
  114. createDirectoryIfMissingVerbose verbosity True tmpTargetDir
  115. withTempDirectory verbosity tmpTargetDir "sdist." $ \tmpDir -> do
  116. let targetDir = tmpDir </> tarBallName pkg'
  117. generateSourceDir targetDir pkg'
  118. targzFile <- createArchive verbosity pkg' mb_lbi tmpDir targetPref
  119. notice verbosity $ "Source tarball created: " ++ targzFile
  120. where
  121. generateSourceDir targetDir pkg' = do
  122. setupMessage verbosity "Building source dist for" (packageId pkg')
  123. prepareTree verbosity pkg' mb_lbi distPref targetDir pps
  124. when snapshot $
  125. overwriteSnapshotPackageDesc verbosity pkg' targetDir
  126. verbosity = fromFlag (sDistVerbosity flags)
  127. snapshot = fromFlag (sDistSnapshot flags)
  128. distPref = fromFlag $ sDistDistPref flags
  129. targetPref = distPref
  130. tmpTargetDir = mkTmpDir distPref
  131. -- |Prepare a directory tree of source files.
  132. prepareTree :: Verbosity -- ^verbosity
  133. -> PackageDescription -- ^info from the cabal file
  134. -> Maybe LocalBuildInfo
  135. -> FilePath -- ^dist dir
  136. -> FilePath -- ^source tree to populate
  137. -> [PPSuffixHandler] -- ^extra preprocessors (includes suffixes)
  138. -> IO ()
  139. prepareTree verbosity pkg_descr0 mb_lbi distPref targetDir pps = do
  140. createDirectoryIfMissingVerbose verbosity True targetDir
  141. -- maybe move the library files into place
  142. withLib $ \Library { exposedModules = modules, libBuildInfo = libBi } ->
  143. prepareDir verbosity pkg_descr distPref targetDir pps modules libBi
  144. -- move the executables into place
  145. withExe $ \Executable { modulePath = mainPath, buildInfo = exeBi } -> do
  146. prepareDir verbosity pkg_descr distPref targetDir pps [] exeBi
  147. srcMainFile <- do
  148. ppFile <- findFileWithExtension (ppSuffixes pps) (hsSourceDirs exeBi) (dropExtension mainPath)
  149. case ppFile of
  150. Nothing -> findFile (hsSourceDirs exeBi) mainPath
  151. Just pp -> return pp
  152. copyFileTo verbosity targetDir srcMainFile
  153. -- move the test suites into place
  154. withTest $ \t -> do
  155. let bi = testBuildInfo t
  156. prep = prepareDir verbosity pkg_descr distPref targetDir pps
  157. case testInterface t of
  158. TestSuiteExeV10 _ mainPath -> do
  159. prep [] bi
  160. srcMainFile <- do
  161. ppFile <- findFileWithExtension (ppSuffixes pps)
  162. (hsSourceDirs bi)
  163. (dropExtension mainPath)
  164. case ppFile of
  165. Nothing -> findFile (hsSourceDirs bi) mainPath
  166. Just pp -> return pp
  167. copyFileTo verbosity targetDir srcMainFile
  168. TestSuiteLibV09 _ m -> do
  169. prep [m] bi
  170. TestSuiteUnsupported tp -> die $ "Unsupported test suite type: " ++ show tp
  171. -- move the benchmarks into place
  172. withBenchmark $ \bm -> do
  173. let bi = benchmarkBuildInfo bm
  174. prep = prepareDir verbosity pkg_descr distPref targetDir pps
  175. case benchmarkInterface bm of
  176. BenchmarkExeV10 _ mainPath -> do
  177. prep [] bi
  178. srcMainFile <- do
  179. ppFile <- findFileWithExtension (ppSuffixes pps)
  180. (hsSourceDirs bi)
  181. (dropExtension mainPath)
  182. case ppFile of
  183. Nothing -> findFile (hsSourceDirs bi) mainPath
  184. Just pp -> return pp
  185. copyFileTo verbosity targetDir srcMainFile
  186. BenchmarkUnsupported tp -> die $ "Unsupported benchmark type: " ++ show tp
  187. flip mapM_ (dataFiles pkg_descr) $ \ filename -> do
  188. files <- matchFileGlob (dataDir pkg_descr </> filename)
  189. let dir = takeDirectory (dataDir pkg_descr </> filename)
  190. createDirectoryIfMissingVerbose verbosity True (targetDir </> dir)
  191. sequence_ [ installOrdinaryFile verbosity file (targetDir </> file)
  192. | file <- files ]
  193. when (not (null (licenseFile pkg_descr))) $
  194. copyFileTo verbosity targetDir (licenseFile pkg_descr)
  195. flip mapM_ (extraSrcFiles pkg_descr) $ \ fpath -> do
  196. files <- matchFileGlob fpath
  197. sequence_
  198. [ do copyFileTo verbosity targetDir file
  199. -- preserve executable bit on extra-src-files like ./configure
  200. perms <- getPermissions file
  201. when (executable perms) --only checks user x bit
  202. (setFileExecutable (targetDir </> file))
  203. | file <- files ]
  204. -- copy the install-include files
  205. withLib $ \ l -> do
  206. let lbi = libBuildInfo l
  207. relincdirs = "." : filter (not.isAbsolute) (includeDirs lbi)
  208. incs <- mapM (findInc relincdirs) (installIncludes lbi)
  209. flip mapM_ incs $ \(_,fpath) ->
  210. copyFileTo verbosity targetDir fpath
  211. -- if the package was configured then we can run platform independent
  212. -- pre-processors and include those generated files
  213. case mb_lbi of
  214. Just lbi | not (null pps) -> do
  215. let lbi' = lbi{ buildDir = targetDir </> buildDir lbi }
  216. withComponentsLBI pkg_descr lbi' $ \c _ ->
  217. preprocessComponent pkg_descr c lbi' True verbosity pps
  218. _ -> return ()
  219. -- setup isn't listed in the description file.
  220. hsExists <- doesFileExist "Setup.hs"
  221. lhsExists <- doesFileExist "Setup.lhs"
  222. if hsExists then copyFileTo verbosity targetDir "Setup.hs"
  223. else if lhsExists then copyFileTo verbosity targetDir "Setup.lhs"
  224. else writeUTF8File (targetDir </> "Setup.hs") $ unlines [
  225. "import Distribution.Simple",
  226. "main = defaultMain"]
  227. -- the description file itself
  228. descFile <- defaultPackageDesc verbosity
  229. installOrdinaryFile verbosity descFile (targetDir </> descFile)
  230. where
  231. pkg_descr = mapAllBuildInfo filterAutogenModule pkg_descr0
  232. filterAutogenModule bi = bi {
  233. otherModules = filter (/=autogenModule) (otherModules bi)
  234. }
  235. autogenModule = autogenModuleName pkg_descr0
  236. findInc [] f = die ("can't find include file " ++ f)
  237. findInc (d:ds) f = do
  238. let path = (d </> f)
  239. b <- doesFileExist path
  240. if b then return (f,path) else findInc ds f
  241. -- We have to deal with all libs and executables, so we have local
  242. -- versions of these functions that ignore the 'buildable' attribute:
  243. withLib action = maybe (return ()) action (library pkg_descr)
  244. withExe action = mapM_ action (executables pkg_descr)
  245. withTest action = mapM_ action (testSuites pkg_descr)
  246. withBenchmark action = mapM_ action (benchmarks pkg_descr)
  247. -- | Prepare a directory tree of source files for a snapshot version.
  248. -- It is expected that the appropriate snapshot version has already been set
  249. -- in the package description, eg using 'snapshotPackage' or 'snapshotVersion'.
  250. --
  251. prepareSnapshotTree :: Verbosity -- ^verbosity
  252. -> PackageDescription -- ^info from the cabal file
  253. -> Maybe LocalBuildInfo
  254. -> FilePath -- ^dist dir
  255. -> FilePath -- ^source tree to populate
  256. -> [PPSuffixHandler] -- ^extra preprocessors (includes suffixes)
  257. -> IO ()
  258. prepareSnapshotTree verbosity pkg mb_lbi distPref targetDir pps = do
  259. prepareTree verbosity pkg mb_lbi distPref targetDir pps
  260. overwriteSnapshotPackageDesc verbosity pkg targetDir
  261. overwriteSnapshotPackageDesc :: Verbosity -- ^verbosity
  262. -> PackageDescription -- ^info from the cabal file
  263. -> FilePath -- ^source tree
  264. -> IO ()
  265. overwriteSnapshotPackageDesc verbosity pkg targetDir = do
  266. -- We could just writePackageDescription targetDescFile pkg_descr,
  267. -- but that would lose comments and formatting.
  268. descFile <- defaultPackageDesc verbosity
  269. withUTF8FileContents descFile $
  270. writeUTF8File (targetDir </> descFile)
  271. . unlines . map (replaceVersion (packageVersion pkg)) . lines
  272. where
  273. replaceVersion :: Version -> String -> String
  274. replaceVersion version line
  275. | "version:" `isPrefixOf` map toLower line
  276. = "version: " ++ display version
  277. | otherwise = line
  278. -- | Modifies a 'PackageDescription' by appending a snapshot number
  279. -- corresponding to the given date.
  280. --
  281. snapshotPackage :: CalendarTime -> PackageDescription -> PackageDescription
  282. snapshotPackage date pkg =
  283. pkg {
  284. package = pkgid { pkgVersion = snapshotVersion date (pkgVersion pkgid) }
  285. }
  286. where pkgid = packageId pkg
  287. -- | Modifies a 'Version' by appending a snapshot number corresponding
  288. -- to the given date.
  289. --
  290. snapshotVersion :: CalendarTime -> Version -> Version
  291. snapshotVersion date version = version {
  292. versionBranch = versionBranch version
  293. ++ [dateToSnapshotNumber date]
  294. }
  295. -- | Given a date produce a corresponding integer representation.
  296. -- For example given a date @18/03/2008@ produce the number @20080318@.
  297. --
  298. dateToSnapshotNumber :: CalendarTime -> Int
  299. dateToSnapshotNumber date = year * 10000
  300. + month * 100
  301. + day
  302. where
  303. year = ctYear date
  304. month = fromEnum (ctMonth date) + 1
  305. day = ctDay date
  306. -- |Create an archive from a tree of source files, and clean up the tree.
  307. createArchive :: Verbosity -- ^verbosity
  308. -> PackageDescription -- ^info from cabal file
  309. -> Maybe LocalBuildInfo -- ^info from configure
  310. -> FilePath -- ^source tree to archive
  311. -> FilePath -- ^name of archive to create
  312. -> IO FilePath
  313. createArchive verbosity pkg_descr mb_lbi tmpDir targetPref = do
  314. let tarBallFilePath = targetPref </> tarBallName pkg_descr <.> "tar.gz"
  315. (tarProg, _) <- requireProgram verbosity tarProgram
  316. (maybe defaultProgramConfiguration withPrograms mb_lbi)
  317. -- Hmm: I could well be skating on thinner ice here by using the -C option (=> GNU tar-specific?)
  318. -- [The prev. solution used pipes and sub-command sequences to set up the paths correctly,
  319. -- which is problematic in a Windows setting.]
  320. rawSystemProgram verbosity tarProg
  321. ["-C", tmpDir, "-czf", tarBallFilePath, tarBallName pkg_descr]
  322. return tarBallFilePath
  323. -- |Move the sources into place based on buildInfo
  324. prepareDir :: Verbosity -- ^verbosity
  325. -> PackageDescription -- ^info from the cabal file
  326. -> FilePath -- ^dist dir
  327. -> FilePath -- ^TargetPrefix
  328. -> [PPSuffixHandler] -- ^ extra preprocessors (includes suffixes)
  329. -> [ModuleName] -- ^Exposed modules
  330. -> BuildInfo
  331. -> IO ()
  332. prepareDir verbosity _pkg _distPref inPref pps modules bi
  333. = do let searchDirs = hsSourceDirs bi
  334. sources <- sequence
  335. [ let file = ModuleName.toFilePath module_
  336. in findFileWithExtension suffixes searchDirs file
  337. >>= maybe (notFound module_) return
  338. | module_ <- modules ++ otherModules bi ]
  339. bootFiles <- sequence
  340. [ let file = ModuleName.toFilePath module_
  341. fileExts = ["hs-boot", "lhs-boot"]
  342. in findFileWithExtension fileExts (hsSourceDirs bi) file
  343. | module_ <- modules ++ otherModules bi ]
  344. let allSources = sources ++ catMaybes bootFiles ++ cSources bi
  345. installOrdinaryFiles verbosity inPref (zip (repeat []) allSources)
  346. where suffixes = ppSuffixes pps ++ ["hs", "lhs"]
  347. notFound m = die $ "Error: Could not find module: " ++ display m
  348. ++ " with any suffix: " ++ show suffixes
  349. copyFileTo :: Verbosity -> FilePath -> FilePath -> IO ()
  350. copyFileTo verbosity dir file = do
  351. let targetFile = dir </> file
  352. createDirectoryIfMissingVerbose verbosity True (takeDirectory targetFile)
  353. installOrdinaryFile verbosity file targetFile
  354. printPackageProblems :: Verbosity -> PackageDescription -> IO ()
  355. printPackageProblems verbosity pkg_descr = do
  356. ioChecks <- checkPackageFiles pkg_descr "."
  357. let pureChecks = checkConfiguredPackage pkg_descr
  358. isDistError (PackageDistSuspicious _) = False
  359. isDistError _ = True
  360. (errors, warnings) = partition isDistError (pureChecks ++ ioChecks)
  361. unless (null errors) $
  362. notice verbosity $ "Distribution quality errors:\n"
  363. ++ unlines (map explanation errors)
  364. unless (null warnings) $
  365. notice verbosity $ "Distribution quality warnings:\n"
  366. ++ unlines (map explanation warnings)
  367. unless (null errors) $
  368. notice verbosity
  369. "Note: the public hackage server would reject this package."
  370. ------------------------------------------------------------
  371. -- | The name of the tarball without extension
  372. --
  373. tarBallName :: PackageDescription -> String
  374. tarBallName = display . packageId
  375. mapAllBuildInfo :: (BuildInfo -> BuildInfo)
  376. -> (PackageDescription -> PackageDescription)
  377. mapAllBuildInfo f pkg = pkg {
  378. library = fmap mapLibBi (library pkg),
  379. executables = fmap mapExeBi (executables pkg),
  380. testSuites = fmap mapTestBi (testSuites pkg),
  381. benchmarks = fmap mapBenchBi (benchmarks pkg)
  382. }
  383. where
  384. mapLibBi lib = lib { libBuildInfo = f (libBuildInfo lib) }
  385. mapExeBi exe = exe { buildInfo = f (buildInfo exe) }
  386. mapTestBi t = t { testBuildInfo = f (testBuildInfo t) }
  387. mapBenchBi bm = bm { benchmarkBuildInfo = f (benchmarkBuildInfo bm) }