Skip to content

Commit

Permalink
Fix input-output-hk#42: use patches for revisions
Browse files Browse the repository at this point in the history
  • Loading branch information
yvan-sraka committed Apr 17, 2023
1 parent 586b692 commit 0d62575
Showing 1 changed file with 30 additions and 9 deletions.
39 changes: 30 additions & 9 deletions app/Foliage/CmdBuild.hs
Original file line number Diff line number Diff line change
@@ -1,15 +1,16 @@
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE OverloadedStrings #-}

module Foliage.CmdBuild (cmdBuild) where

import Codec.Archive.Tar qualified as Tar
import Codec.Archive.Tar.Entry qualified as Tar
import Codec.Compression.GZip qualified as GZip
import Control.Monad (unless, void, when)
import Control.Monad (foldM, unless, void, when)
import Data.Aeson qualified as Aeson
import Data.ByteString qualified as BS
import Data.ByteString.Lazy qualified as BL
import Data.ByteString.Char8 qualified as BS
import Data.ByteString.Lazy.Char8 qualified as BL
import Data.List (sortOn)
import Data.Maybe (fromMaybe)
import Data.Text qualified as T
Expand Down Expand Up @@ -101,9 +102,10 @@ buildAction

void $ forP packageVersions $ makePackageVersionPage outputDir

void $ forP packageVersions $ \PreparedPackageVersion {pkgId, cabalFilePath} -> do
let PackageIdentifier {pkgName, pkgVersion} = pkgId
copyFileChanged cabalFilePath (outputDir </> "index" </> prettyShow pkgName </> prettyShow pkgVersion </> prettyShow pkgName <.> "cabal")
void $
forP packageVersions $ \PreparedPackageVersion {pkgId, cabalFilePath} -> do
let PackageIdentifier {pkgName, pkgVersion} = pkgId
copyFileChanged cabalFilePath (outputDir </> "index" </> prettyShow pkgName </> prettyShow pkgVersion </> prettyShow pkgName <.> "cabal")

cabalEntries <-
foldMap
Expand All @@ -113,9 +115,22 @@ buildAction
cf <- prepareIndexPkgCabal pkgId cabalFileTimestamp originalCabalFilePath

-- all revised cabal files, with their timestamp
revcf <- for cabalFileRevisions $ uncurry (prepareIndexPkgCabal pkgId)

return $ cf : revcf
revcf <-
foldM
( \(lastRevisionPath, cabalFiles) (ts, revisionPath) -> do
if takeExtension originalCabalFilePath `elem` [".diff", ".patch"]
then do
patchedRevisionPath <- applyPatch lastRevisionPath revisionPath
preparedCabal <- prepareIndexPkgCabal pkgId ts patchedRevisionPath
return (patchedRevisionPath, cabalFiles ++ [preparedCabal])
else do
preparedCabal <- prepareIndexPkgCabal pkgId ts revisionPath
return (revisionPath, cabalFiles ++ [preparedCabal])
)
(originalCabalFilePath, [])
(sortOn fst cabalFileRevisions)

return $ cf : snd revcf
)
packageVersions

Expand Down Expand Up @@ -312,3 +327,9 @@ mkTarEntry contents indexFile timestamp =
anchorPath :: Path Absolute -> (RepoLayout -> RepoPath) -> FilePath
anchorPath outputDirRoot p =
toFilePath $ anchorRepoPathLocally outputDirRoot $ p hackageRepoLayout

applyPatch :: FilePath -> FilePath -> Action FilePath
applyPatch originalFilePath patchFilePath = do
withTempFile $ \outputFilePath -> do
cmd_ ["patch", "-i", patchFilePath, "-o", outputFilePath, originalFilePath]
return outputFilePath

0 comments on commit 0d62575

Please sign in to comment.