Merge pull request #205 from ryantm/updatescript

use passthru.updateScript
This commit is contained in:
Ryan Mulligan 2020-07-31 21:33:11 -07:00 committed by GitHub
commit c15ebd738c
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
7 changed files with 246 additions and 180 deletions

View File

@ -87,8 +87,8 @@ cleanup bName = do
runProcessNoIndexIssue_ (delete1 bName)
<|> liftIO (T.putStrLn ("Couldn't delete " <> bName))
diff :: MonadIO m => ExceptT Text m Text
diff = readProcessInterleavedNoIndexIssue_ $ procGit ["diff"]
diff :: MonadIO m => Text -> ExceptT Text m Text
diff branch = readProcessInterleavedNoIndexIssue_ $ procGit ["diff", T.unpack branch]
staleFetchHead :: MonadIO m => m Bool
staleFetchHead =
@ -149,13 +149,14 @@ setupNixpkgs githubt = do
_ <- runExceptT $ cleanAndResetTo "master"
System.Posix.Env.setEnv "NIX_PATH" ("nixpkgs=" <> fp) True
checkoutAtMergeBase :: MonadIO m => Text -> ExceptT Text m ()
checkoutAtMergeBase :: MonadIO m => Text -> ExceptT Text m Text
checkoutAtMergeBase bName = do
base <-
readProcessInterleavedNoIndexIssue_
(procGit ["merge-base", "upstream/master", "upstream/staging"])
& fmapRT T.strip
runProcessNoIndexIssue_ (checkout bName base)
return base
checkAutoUpdateBranchDoesntExist :: MonadIO m => Text -> ExceptT Text m ()
checkAutoUpdateBranchDoesntExist pName = do

View File

@ -25,12 +25,14 @@ module Nix
getSrcUrl,
getSrcUrls,
hasPatchNamed,
hasUpdateScript,
lookupAttrPath,
nixEvalET,
numberOfFetchers,
numberOfHashes,
parseStringList,
resultLink,
runUpdateScript,
sha256Zero,
version,
Raw (..),
@ -45,6 +47,7 @@ import qualified Data.Vector as V
import Language.Haskell.TH.Env (envQ)
import OurPrelude
import qualified Polysemy.Error as Error
import qualified System.Process.Typed as TP
import qualified Process
import qualified Process as P
import System.Exit
@ -356,3 +359,22 @@ hasPatchNamed :: MonadIO m => Text -> Text -> ExceptT Text m Bool
hasPatchNamed attrPath name = do
ps <- getPatches attrPath
return $ name `T.isInfixOf` ps
hasUpdateScript :: MonadIO m => Text -> ExceptT Text m Bool
hasUpdateScript attrPath = do
result <-
nixEvalET
(EvalOptions NoRaw (Env []))
( "(let pkgs = import ./. {}; in builtins.hasAttr \"updateScript\" pkgs."
<> attrPath
<> ")"
)
case result of
"true" -> return True
_ -> return False
runUpdateScript :: MonadIO m => Text -> ExceptT Text m (ExitCode, Text)
runUpdateScript attrPath = do
ourReadProcessInterleaved $
TP.setStdin (TP.byteStringInput "\n") $
proc "nix-shell" ["maintainers/scripts/update.nix", "--argstr", "package", T.unpack attrPath]

View File

@ -1,4 +1,6 @@
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ViewPatterns #-}
module Rewrite
@ -24,9 +26,10 @@ import OurPrelude
import qualified Polysemy.Error as Error
import Polysemy.Output (Output, output)
import qualified Process
import System.Exit
import Utils (UpdateEnv (..))
import qualified Utils
( UpdateEnv (..),
runLog,
( runLog,
stripQuotes,
)
import Prelude hiding (log)
@ -51,39 +54,50 @@ data Args = Args
{ updateEnv :: Utils.UpdateEnv,
attrPath :: Text,
derivationFile :: FilePath,
derivationContents :: Text
derivationContents :: Text,
hasUpdateScript :: Bool
}
type Rewriter = (Text -> IO ()) -> Args -> ExceptT Text IO (Maybe Text)
type Plan = [(Text, Rewriter)]
plan :: Plan
plan =
[ ("version", version),
("rustCrateVersion", rustCrateVersion),
("golangModuleVersion", golangModuleVersion),
("updateScript", updateScript),
("", quotedUrlsET) -- Don't change the logger
--("redirectedUrl", Rewrite.redirectedUrls)
]
runAll :: (Text -> IO ()) -> Args -> ExceptT Text IO [Text]
runAll log rwArgs = do
let rewriters =
[ ("version", Rewrite.version),
("rustCrateVersion", Rewrite.rustCrateVersion),
("golangModuleVersion", Rewrite.golangModuleVersion),
("", Rewrite.quotedUrlsET) -- Don't change the logger
--("redirectedUrl", Rewrite.redirectedUrls)
]
msgs <- forM rewriters $ \(name, f) -> do
runAll log args = do
msgs <- forM plan $ \(name, f) -> do
let log' msg =
if T.null name
then log msg
else log $ ("[" <> name <> "] ") <> msg
lift $ log' "" -- Print initial empty message to signal start of rewriter
f log' rwArgs
f log' args
return $ catMaybes msgs
--------------------------------------------------------------------------------
-- The canonical updater: updates the src attribute and recomputes the sha256
version :: MonadIO m => (Text -> m ()) -> Args -> ExceptT Text m (Maybe Text)
version log args@(Args _ _ _ drvContents) = do
if Nix.numberOfFetchers drvContents > 1 || Nix.numberOfHashes drvContents > 1
then do
lift $ log "generic version rewriter does not support multiple hashes"
return Nothing
else do
srcVersionFix args
lift $ log "updated version and sha256"
return $ Just "Version update"
version log args@Args {..} = do
if
| Nix.numberOfFetchers derivationContents > 1 || Nix.numberOfHashes derivationContents > 1 -> do
lift $ log "generic version rewriter does not support multiple hashes"
return Nothing
| hasUpdateScript -> do
lift $ log "skipping because derivation has updateScript"
return Nothing
| otherwise -> do
srcVersionFix args
lift $ log "updated version and sha256"
return $ Just "Version update"
--------------------------------------------------------------------------------
-- Rewrite meta.homepage (and eventually other URLs) to be quoted if not
@ -92,17 +106,18 @@ quotedUrls ::
Members '[Process.Process, File.File, Error Text, Output Text] r =>
Args ->
Sem r (Maybe Text)
quotedUrls (Args _ attrPth drvFile _) = do
quotedUrls Args {..} = do
output "[quotedUrls]"
homepage <- Nix.getHomepage attrPth
homepage <- Nix.getHomepage attrPath
stripped <- case Utils.stripQuotes homepage of
Nothing -> throw "Could not strip url! This should never happen!"
Just x -> pure x
let goodHomepage = "homepage = " <> homepage <> ";"
urlReplaced1 <- File.replace ("homepage = " <> stripped <> ";") goodHomepage drvFile
urlReplaced2 <- File.replace ("homepage = " <> stripped <> " ;") goodHomepage drvFile
urlReplaced3 <- File.replace ("homepage =" <> stripped <> ";") goodHomepage drvFile
urlReplaced4 <- File.replace ("homepage =" <> stripped <> "; ") goodHomepage drvFile
let replacer = \target -> File.replace target goodHomepage derivationFile
urlReplaced1 <- replacer ("homepage = " <> stripped <> ";")
urlReplaced2 <- replacer ("homepage = " <> stripped <> " ;")
urlReplaced3 <- replacer ("homepage =" <> stripped <> ";")
urlReplaced4 <- replacer ("homepage =" <> stripped <> "; ")
if urlReplaced1 || urlReplaced2 || urlReplaced3 || urlReplaced4
then do
output "[quotedUrls]: added quotes to meta.homepage"
@ -126,8 +141,8 @@ quotedUrlsET log rwArgs =
--------------------------------------------------------------------------------
-- Redirect homepage when moved.
redirectedUrls :: MonadIO m => (Text -> m ()) -> Args -> ExceptT Text m (Maybe Text)
redirectedUrls log (Args _ attrPth drvFile _) = do
unstripped <- Nix.getHomepageET attrPth
redirectedUrls log Args {..} = do
unstripped <- Nix.getHomepageET attrPath
homepage <- case Utils.stripQuotes unstripped of
Nothing -> throwE "Could not strip homepage! This should never happen!"
Just x -> pure x
@ -146,7 +161,7 @@ redirectedUrls log (Args _ attrPth drvFile _) = do
lift $ log "Server did not return a location"
return Nothing
Just (decodeUtf8 -> newHomepage) -> do
_ <- File.replaceIO homepage newHomepage drvFile
_ <- File.replaceIO homepage newHomepage derivationFile
lift $ log "Replaced homepage"
return $
Just $
@ -163,72 +178,94 @@ redirectedUrls log (Args _ attrPth drvFile _) = do
-- This is basically `version` above, but with a second pass to also update the
-- cargoSha256 vendor hash.
rustCrateVersion :: MonadIO m => (Text -> m ()) -> Args -> ExceptT Text m (Maybe Text)
rustCrateVersion log args@(Args _ attrPth drvFile drvContents) = do
if not (T.isInfixOf "cargoSha256" drvContents)
then do
lift $ log "No cargoSha256 found"
return Nothing
else do
-- This starts the same way `version` does, minus the assert
srcVersionFix args
-- But then from there we need to do this a second time for the cargoSha256!
oldCargoSha256 <- Nix.getAttr Nix.Raw "cargoSha256" attrPth
_ <- lift $ File.replaceIO oldCargoSha256 Nix.sha256Zero drvFile
newCargoSha256 <- Nix.getHashFromBuild attrPth
when (oldCargoSha256 == newCargoSha256) $ throwE "cargoSha256 hashes equal; no update necessary"
lift . log $ "Replacing cargoSha256 with " <> newCargoSha256
_ <- lift $ File.replaceIO Nix.sha256Zero newCargoSha256 drvFile
-- Ensure the package actually builds and passes its tests
Nix.build attrPth
lift $ log "Finished updating Crate version and replacing hashes"
return $ Just "Rust version update"
rustCrateVersion log args@Args {..} = do
if
| not (T.isInfixOf "cargoSha256" derivationContents) -> do
lift $ log "No cargoSha256 found"
return Nothing
| hasUpdateScript -> do
lift $ log "skipping because derivation has updateScript"
return Nothing
| otherwise -> do
-- This starts the same way `version` does, minus the assert
srcVersionFix args
-- But then from there we need to do this a second time for the cargoSha256!
oldCargoSha256 <- Nix.getAttr Nix.Raw "cargoSha256" attrPath
_ <- lift $ File.replaceIO oldCargoSha256 Nix.sha256Zero derivationFile
newCargoSha256 <- Nix.getHashFromBuild attrPath
when (oldCargoSha256 == newCargoSha256) $ throwE "cargoSha256 hashes equal; no update necessary"
lift . log $ "Replacing cargoSha256 with " <> newCargoSha256
_ <- lift $ File.replaceIO Nix.sha256Zero newCargoSha256 derivationFile
-- Ensure the package actually builds and passes its tests
Nix.build attrPath
lift $ log "Finished updating Crate version and replacing hashes"
return $ Just "Rust version update"
--------------------------------------------------------------------------------
-- Rewrite Golang packages with buildGoModule
-- This is basically `version` above, but with a second pass to also update the
-- vendorSha256 go vendor hash.
golangModuleVersion :: MonadIO m => (Text -> m ()) -> Args -> ExceptT Text m (Maybe Text)
golangModuleVersion log args@(Args _ attrPth drvFile drvContents) = do
if not (T.isInfixOf "buildGoModule" drvContents && T.isInfixOf "vendorSha256" drvContents)
then do
lift $ log "Not a buildGoModule package with vendorSha256"
golangModuleVersion log args@Args {..} = do
if
| not (T.isInfixOf "buildGoModule" derivationContents && T.isInfixOf "vendorSha256" derivationContents) -> do
lift $ log "Not a buildGoModule package with vendorSha256"
return Nothing
| hasUpdateScript -> do
lift $ log "skipping because derivation has updateScript"
return Nothing
| otherwise -> do
-- This starts the same way `version` does, minus the assert
srcVersionFix args
-- But then from there we need to do this a second time for the vendorSha256!
-- Note that explicit `null` cannot be coerced to a string by nix eval --raw
oldVendorSha256 <- (Nix.getAttr Nix.Raw "vendorSha256" attrPath <|> Nix.getAttr Nix.NoRaw "vendorSha256" attrPath)
lift . log $ "Found old vendorSha256 = " <> oldVendorSha256
original <- liftIO $ T.readFile derivationFile
_ <- lift $ File.replaceIO ("\"" <> oldVendorSha256 <> "\"") "null" derivationFile
ok <- runExceptT $ Nix.build attrPath
_ <-
if isLeft ok
then do
_ <- liftIO $ T.writeFile derivationFile original
_ <- lift $ File.replaceIO oldVendorSha256 Nix.sha256Zero derivationFile
newVendorSha256 <- Nix.getHashFromBuild attrPath
_ <- lift $ File.replaceIO Nix.sha256Zero newVendorSha256 derivationFile
-- Note that on some small bumps, this may not actually change if go.sum did not
lift . log $ "Replaced vendorSha256 with " <> newVendorSha256
else do
lift . log $ "Set vendorSha256 to null"
-- Ensure the package actually builds and passes its tests
Nix.build attrPath
lift $ log "Finished updating vendorSha256"
return $ Just "Golang update"
--------------------------------------------------------------------------------
-- Calls passthru.updateScript
updateScript :: MonadIO m => (Text -> m ()) -> Args -> ExceptT Text m (Maybe Text)
updateScript log args = do
(exitCode, msg) <- Nix.runUpdateScript (attrPath args)
case exitCode of
ExitSuccess -> do
lift $ log "Success"
lift $ log msg
return $ Just "Ran passthru.UpdateScript"
ExitFailure num -> do
lift $ log $ "Failed with exit code " <> tshow num
lift $ log msg
return Nothing
else do
-- This starts the same way `version` does, minus the assert
srcVersionFix args
-- But then from there we need to do this a second time for the vendorSha256!
-- Note that explicit `null` cannot be coerced to a string by nix eval --raw
oldVendorSha256 <- (Nix.getAttr Nix.Raw "vendorSha256" attrPth <|> Nix.getAttr Nix.NoRaw "vendorSha256" attrPth)
lift . log $ "Found old vendorSha256 = " <> oldVendorSha256
original <- liftIO $ T.readFile drvFile
_ <- lift $ File.replaceIO ("\"" <> oldVendorSha256 <> "\"") "null" drvFile
ok <- runExceptT $ Nix.build attrPth
_ <-
if isLeft ok
then do
_ <- liftIO $ T.writeFile drvFile original
_ <- lift $ File.replaceIO oldVendorSha256 Nix.sha256Zero drvFile
newVendorSha256 <- Nix.getHashFromBuild attrPth
_ <- lift $ File.replaceIO Nix.sha256Zero newVendorSha256 drvFile
-- Note that on some small bumps, this may not actually change if go.sum did not
lift . log $ "Replaced vendorSha256 with " <> newVendorSha256
else do
lift . log $ "Set vendorSha256 to null"
-- Ensure the package actually builds and passes its tests
Nix.build attrPth
lift $ log "Finished updating vendorSha256"
return $ Just "Golang update"
--------------------------------------------------------------------------------
-- Common helper functions and utilities
-- Helper to update version and src attributes, re-computing the sha256.
-- This is done by the generic version upgrader, but is also a sub-component of some of the others.
srcVersionFix :: MonadIO m => Args -> ExceptT Text m ()
srcVersionFix (Args env attrPth drvFile _) = do
oldHash <- Nix.getOldHash attrPth
_ <- lift $ File.replaceIO (Utils.oldVersion env) (Utils.newVersion env) drvFile
_ <- lift $ File.replaceIO oldHash Nix.sha256Zero drvFile
newHash <- Nix.getHashFromBuild attrPth
srcVersionFix Args {..} = do
let UpdateEnv {..} = updateEnv
oldHash <- Nix.getOldHash attrPath
_ <- lift $ File.replaceIO oldVersion newVersion derivationFile
_ <- lift $ File.replaceIO oldHash Nix.sha256Zero derivationFile
newHash <- Nix.getHashFromBuild attrPath
when (oldHash == newHash) $ throwE "Hashes equal; no update necessary"
_ <- lift $ File.replaceIO Nix.sha256Zero newHash drvFile
_ <- lift $ File.replaceIO Nix.sha256Zero newHash derivationFile
return ()

View File

@ -2,6 +2,7 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -fno-warn-type-defaults #-}
@ -17,7 +18,6 @@ module Update
)
where
import qualified Skiplist
import CVE (CVE, cveID, cveLI)
import qualified Check
import Control.Concurrent
@ -38,6 +38,7 @@ import qualified NixpkgsReview
import OurPrelude
import Outpaths
import qualified Rewrite
import qualified Skiplist
import qualified Time
import Utils
( Options (..),
@ -48,6 +49,7 @@ import Utils
logDir,
parseUpdates,
prTitle,
whenBatch,
)
import qualified Version
import Prelude hiding (log)
@ -191,37 +193,44 @@ updatePackageBatch ::
UpdateEnv ->
IORef MergeBaseOutpathsInfo ->
IO (Either Text ())
updatePackageBatch log updateEnv mergeBaseOutpathsContext =
updatePackageBatch log updateEnv@UpdateEnv {..} mergeBaseOutpathsContext =
runExceptT $ do
let pr = doPR . options $ updateEnv
--
let pr = doPR options
-- Filters that don't need git
Skiplist.packageName (packageName updateEnv)
Nix.assertNewerVersion updateEnv
--
whenBatch updateEnv do
Skiplist.packageName packageName
-- Update our git checkout
Git.fetchIfStale <|> liftIO (T.putStrLn "Failed to fetch.")
when pr $
Git.checkAutoUpdateBranchDoesntExist (packageName updateEnv)
Git.cleanAndResetTo "master"
--
-- Filters: various cases where we shouldn't update the package
attrPath <- Nix.lookupAttrPath updateEnv
when pr $
GH.checkExistingUpdatePR updateEnv attrPath
Skiplist.attrPath attrPath
Version.assertCompatibleWithPathPin updateEnv attrPath
hasUpdateScript <- Nix.hasUpdateScript attrPath
srcUrls <- Nix.getSrcUrls attrPath
Skiplist.srcUrl srcUrls
whenBatch updateEnv do
Skiplist.attrPath attrPath
when pr do
Git.checkAutoUpdateBranchDoesntExist packageName
GH.checkExistingUpdatePR updateEnv attrPath
unless hasUpdateScript do
Nix.assertNewerVersion updateEnv
Version.assertCompatibleWithPathPin updateEnv attrPath
Skiplist.srcUrl srcUrls
derivationFile <- Nix.getDerivationFile attrPath
assertNotUpdatedOn updateEnv derivationFile "master"
assertNotUpdatedOn updateEnv derivationFile "staging"
assertNotUpdatedOn updateEnv derivationFile "staging-next"
assertNotUpdatedOn updateEnv derivationFile "python-unstable"
--
unless hasUpdateScript do
assertNotUpdatedOn updateEnv derivationFile "master"
assertNotUpdatedOn updateEnv derivationFile "staging"
assertNotUpdatedOn updateEnv derivationFile "staging-next"
assertNotUpdatedOn updateEnv derivationFile "python-unstable"
-- Calculate output paths for rebuilds and our merge base
Git.checkoutAtMergeBase (branchName updateEnv)
let calcOutpaths = calculateOutpaths . options $ updateEnv
mergeBase <- Git.checkoutAtMergeBase (branchName updateEnv)
let calcOutpaths = calculateOutpaths options
oneHourAgo <- liftIO $ runM $ Time.runIO Time.oneHourAgo
mergeBaseOutpathsInfo <- liftIO $ readIORef mergeBaseOutpathsContext
mergeBaseOutpathSet <-
@ -236,45 +245,76 @@ updatePackageBatch log updateEnv mergeBaseOutpathsContext =
if calcOutpaths
then return $ mergeBaseOutpaths mergeBaseOutpathsInfo
else return $ dummyOutpathSetBefore attrPath
--
-- Get the original values for diffing purposes
derivationContents <- liftIO $ T.readFile derivationFile
oldHash <- Nix.getOldHash attrPath
oldSrcUrl <- Nix.getSrcUrl attrPath
--
oldVerMay <- rightMay `fmapRT` (lift $ runExceptT $ Nix.getAttr Nix.Raw "version" attrPath)
tryAssert
"The derivation has no 'version' attribute, so do not know how to figure out the version while doing an updateScript update"
(not hasUpdateScript || isJust oldVerMay)
-- One final filter
Skiplist.content derivationContents
--
unless hasUpdateScript do
Skiplist.content derivationContents
----------------------------------------------------------------------------
-- UPDATES
-- At this point, we've stashed the old derivation contents and validated
-- that we actually should be touching this file. Get to work processing the
-- various rewrite functions!
let rwArgs = Rewrite.Args updateEnv attrPath derivationFile derivationContents
rewriteMsgs <- Rewrite.runAll log rwArgs
----------------------------------------------------------------------------
--
-- At this point, we've stashed the old derivation contents and
-- validated that we actually should be rewriting something. Get
-- to work processing the various rewrite functions!
rewriteMsgs <- Rewrite.runAll log Rewrite.Args {..}
----------------------------------------------------------------------------
-- Compute the diff and get updated values
diffAfterRewrites <- Git.diff
diffAfterRewrites <- Git.diff mergeBase
lift . log $ "Diff after rewrites:\n" <> diffAfterRewrites
updatedDerivationContents <- liftIO $ T.readFile derivationFile
newSrcUrl <- Nix.getSrcUrl attrPath
newHash <- Nix.getHash attrPath
newVerMay <- rightMay `fmapRT` (lift $ runExceptT $ Nix.getAttr Nix.Raw "version" attrPath)
tryAssert
"The derivation has no 'version' attribute, so do not know how to figure out the version while doing an updateScript update"
(not hasUpdateScript || isJust newVerMay)
-- Sanity checks to make sure the PR is worth opening
when (derivationContents == updatedDerivationContents) $ throwE "No rewrites performed on derivation."
when (oldSrcUrl == newSrcUrl) $ throwE "Source url did not change. "
when (oldHash == newHash) $ throwE "Hashes equal; no update necessary"
unless hasUpdateScript do
when (derivationContents == updatedDerivationContents) $ throwE "No rewrites performed on derivation."
when (oldSrcUrl == newSrcUrl) $ throwE "Source url did not change. "
when (oldHash == newHash) $ throwE "Hashes equal; no update necessary"
editedOutpathSet <- if calcOutpaths then currentOutpathSet else return $ dummyOutpathSetAfter attrPath
let opDiff = S.difference mergeBaseOutpathSet editedOutpathSet
let numPRebuilds = numPackageRebuilds opDiff
Skiplist.python numPRebuilds derivationContents
whenBatch updateEnv do
Skiplist.python numPRebuilds derivationContents
when (numPRebuilds == 0) (throwE "Update edits cause no rebuilds.")
Nix.build attrPath
--
-- Update updateEnv if using updateScript
updateEnv' <-
if hasUpdateScript
then do
-- Already checked that these are Just above.
let Just oldVer = oldVerMay
let Just newVer = newVerMay
return $
UpdateEnv
packageName
oldVer
newVer
(Just "passthru.updateScript")
options
else return updateEnv
--
-- Publish the result
lift . log $ "Successfully finished processing"
result <- Nix.resultLink
publishPackage log updateEnv oldSrcUrl newSrcUrl attrPath result (Just opDiff) rewriteMsgs
publishPackage log updateEnv' oldSrcUrl newSrcUrl attrPath result (Just opDiff) rewriteMsgs
Git.cleanAndResetTo "master"
publishPackage ::
@ -420,8 +460,11 @@ prMessage updateEnv isBroken metaDescription metaHomepage metaChangelog rewriteM
|]
pat link = [interpolate|This update was made based on information from $link.|]
sourceLinkInfo = maybe "" pat $ sourceURL updateEnv
ghUser = GH.untagName . githubUser . options $ updateEnv
batch = batchUpdate . options $ updateEnv
automatic = if batch then "Automatic" else "Semi-automatic"
in [interpolate|
Semi-automatic update generated by [nixpkgs-update](https://github.com/ryantm/nixpkgs-update) tools. $sourceLinkInfo
$automatic update generated by [nixpkgs-update](https://github.com/ryantm/nixpkgs-update) tools. $sourceLinkInfo
$brokenMsg
$metaDescriptionLine
@ -473,7 +516,7 @@ prMessage updateEnv isBroken metaDescription metaHomepage metaChangelog rewriteM
$cachixTestInstructions
```
nix-build -A $attrPath https://github.com/r-ryantm/nixpkgs/archive/$commitHash.tar.gz
nix-build -A $attrPath https://github.com/$ghUser/nixpkgs/archive/$commitHash.tar.gz
```
After you've downloaded or built it, look at the files and if there are any, run the binaries:
@ -615,57 +658,16 @@ doCachix log updateEnv resultPath =
lift $ log "skipping cachix"
return "Build yourself:"
-- FIXME: We should delete updatePackageBatch, and instead have the updateLoop
-- just call updatePackage, so we aren't maintaining two parallel
-- implementations!
updatePackage ::
Options ->
Text ->
IO (Either Text ())
updatePackage o updateInfo = do
runExceptT $ do
let (p, oldV, newV, url) = head (rights (parseUpdates updateInfo))
let updateEnv = UpdateEnv p oldV newV url o
let log = T.putStrLn
liftIO $ notifyOptions log o
--
-- Update our git checkout and swap onto the update branch
Git.fetchIfStale <|> liftIO (T.putStrLn "Failed to fetch.")
Git.cleanAndResetTo "master"
Git.checkoutAtMergeBase (branchName updateEnv)
-- Gather some basic information
Nix.assertNewerVersion updateEnv
attrPath <- Nix.lookupAttrPath updateEnv
Version.assertCompatibleWithPathPin updateEnv attrPath
derivationFile <- Nix.getDerivationFile attrPath
--
-- Get the original values for diffing purposes
derivationContents <- liftIO $ T.readFile derivationFile
oldHash <- Nix.getOldHash attrPath
oldSrcUrl <- Nix.getSrcUrl attrPath
--
----------------------------------------------------------------------------
-- UPDATES
-- At this point, we've stashed the old derivation contents and validated
-- that we actually should be touching this file. Get to work processing the
-- various rewrite functions!
let rwArgs = Rewrite.Args updateEnv attrPath derivationFile derivationContents
msgs <- Rewrite.runAll log rwArgs
----------------------------------------------------------------------------
--
-- Compute the diff and get updated values
diffAfterRewrites <- Git.diff
lift . log $ "Diff after rewrites:\n" <> diffAfterRewrites
updatedDerivationContents <- liftIO $ T.readFile derivationFile
newSrcUrl <- Nix.getSrcUrl attrPath
newHash <- Nix.getHash attrPath
-- Sanity checks to make sure the PR is worth opening
when (derivationContents == updatedDerivationContents) $ throwE "No rewrites performed on derivation."
when (oldSrcUrl == newSrcUrl) $ throwE "Source url did not change. "
when (oldHash == newHash) $ throwE "Hashes equal; no update necessary"
Nix.build attrPath
--
-- Publish the result
lift . log $ "Successfully finished processing"
result <- Nix.resultLink
publishPackage log updateEnv oldSrcUrl newSrcUrl attrPath result Nothing msgs
let (p, oldV, newV, url) = head (rights (parseUpdates updateInfo))
let updateEnv = UpdateEnv p oldV newV url o
let log = T.putStrLn
liftIO $ notifyOptions log o
twoHoursAgo <- runM $ Time.runIO Time.twoHoursAgo
mergeBaseOutpathSet <-
liftIO $ newIORef (MergeBaseOutpathsInfo twoHoursAgo S.empty)
updatePackageBatch log updateEnv mergeBaseOutpathSet

View File

@ -25,6 +25,7 @@ module Utils
srcOrMain,
stripQuotes,
tRead,
whenBatch,
)
where
@ -121,6 +122,9 @@ data UpdateEnv = UpdateEnv
options :: Options
}
whenBatch :: Applicative f => UpdateEnv -> f () -> f ()
whenBatch updateEnv = when (batchUpdate . options $ updateEnv)
prTitle :: UpdateEnv -> Text -> Text
prTitle updateEnv attrPath =
let oV = oldVersion updateEnv

View File

@ -23,10 +23,10 @@ spec = do
it "quotes an unquoted meta.homepage URL" do
nixQuotedHomepageBad <- T.readFile "test_data/quoted_homepage_bad.nix"
nixQuotedHomepageGood <- T.readFile "test_data/quoted_homepage_good.nix"
let options = Utils.Options False False "" "" False False False False
let options = Utils.Options False False "r-ryantm" "" False False False False
let updateEnv = Utils.UpdateEnv "inadyn" "2.5" "2.6" Nothing options
-- TODO test correct file is being read
let rwArgs = Rewrite.Args updateEnv "inadyn" undefined undefined
let rwArgs = Rewrite.Args updateEnv "inadyn" undefined undefined False
(logs, (newContents, result)) <-
( runFinal
. embedToFinal

View File

@ -18,7 +18,7 @@ spec :: Spec
spec = do
describe "PR message" do
-- Common mock options
let options = Utils.Options False False "" "" False False False False
let options = Utils.Options False False "r-ryantm" "" False False False False
let updateEnv = Utils.UpdateEnv "foobar" "1.0" "1.1" (Just "https://update-site.com") options
let isBroken = False
let metaDescription = "\"Foobar package description\""