This commit is contained in:
Ryan Mulligan 2020-12-11 13:43:56 -08:00
parent 4e02df0618
commit 80e6143f64
4 changed files with 26 additions and 24 deletions

View File

@ -1,5 +1,6 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE NoImplicitPrelude #-}
module Git module Git
( checkAutoUpdateBranchDoesntExist, ( checkAutoUpdateBranchDoesntExist,
@ -31,7 +32,8 @@ import Data.Time.Clock (addUTCTime, getCurrentTime)
import qualified Data.Vector as V import qualified Data.Vector as V
import Language.Haskell.TH.Env (envQ) import Language.Haskell.TH.Env (envQ)
import OurPrelude hiding (throw) import OurPrelude hiding (throw)
import System.Directory (doesDirectoryExist, doesFileExist, getModificationTime, getCurrentDirectory, setCurrentDirectory) import RIO
import System.Directory (doesDirectoryExist, doesFileExist, getCurrentDirectory, getModificationTime, setCurrentDirectory)
import System.Environment (getEnv) import System.Environment (getEnv)
import System.Environment.XDG.BaseDir (getUserCacheDir) import System.Environment.XDG.BaseDir (getUserCacheDir)
import System.Exit import System.Exit
@ -132,7 +134,7 @@ push updateEnv =
) )
) )
nixpkgsDir :: IO FilePath nixpkgsDir :: MonadIO m => m FilePath
nixpkgsDir = do nixpkgsDir = do
inNixpkgs <- inNixpkgsRepo inNixpkgs <- inNixpkgsRepo
if inNixpkgs if inNixpkgs
@ -183,7 +185,7 @@ checkAutoUpdateBranchDoesntExist pName = do
(("origin/" <> branchPrefix <> pName) `elem` remoteBranches) (("origin/" <> branchPrefix <> pName) `elem` remoteBranches)
(throwE "Update branch already on origin.") (throwE "Update branch already on origin.")
inNixpkgsRepo :: IO Bool inNixpkgsRepo :: MonadIO m => m Bool
inNixpkgsRepo = do inNixpkgsRepo = do
currentDir <- getCurrentDirectory currentDir <- getCurrentDirectory
doesFileExist (currentDir <> "/nixos/release.nix") doesFileExist (currentDir <> "/nixos/release.nix")

View File

@ -7,7 +7,6 @@ module OurPrelude
(<>), (<>),
(<&>), (<&>),
(&), (&),
module Control.Error,
module Control.Monad.Except, module Control.Monad.Except,
module Control.Monad.Trans.Class, module Control.Monad.Trans.Class,
module Control.Monad.IO.Class, module Control.Monad.IO.Class,

View File

@ -5,6 +5,7 @@
{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-type-defaults #-} {-# OPTIONS_GHC -fno-warn-type-defaults #-}
module Update module Update
@ -21,9 +22,7 @@ where
import CVE (CVE, cveID, cveLI) import CVE (CVE, cveID, cveLI)
import qualified Check import qualified Check
import Control.Concurrent
import qualified Data.ByteString.Lazy.Char8 as BSL import qualified Data.ByteString.Lazy.Char8 as BSL
import Data.IORef
import Data.Maybe (fromJust) import Data.Maybe (fromJust)
import qualified Data.Set as S import qualified Data.Set as S
import qualified Data.Text as T import qualified Data.Text as T
@ -38,6 +37,7 @@ import qualified Nix
import qualified NixpkgsReview import qualified NixpkgsReview
import OurPrelude import OurPrelude
import Outpaths import Outpaths
import RIO
import qualified Rewrite import qualified Rewrite
import qualified Skiplist import qualified Skiplist
import qualified Time import qualified Time
@ -85,8 +85,9 @@ getLog o = do
return log return log
else return T.putStrLn else return T.putStrLn
notifyOptions :: (Text -> IO ()) -> Options -> IO () notifyOptions :: RIO Options ()
notifyOptions log o = do notifyOptions = do
o <- ask
let repr f = if f o then "YES" else "NO" let repr f = if f o then "YES" else "NO"
let ghUser = GH.untagName . githubUser $ o let ghUser = GH.untagName . githubUser $ o
let pr = repr doPR let pr = repr doPR
@ -94,7 +95,7 @@ notifyOptions log o = do
let cve = repr makeCVEReport let cve = repr makeCVEReport
let review = repr runNixpkgsReview let review = repr runNixpkgsReview
npDir <- tshow <$> Git.nixpkgsDir npDir <- tshow <$> Git.nixpkgsDir
log $ logInfo $
[interpolate| [interpolate|
Configured Nixpkgs-Update Options: Configured Nixpkgs-Update Options:
---------------------------------- ----------------------------------
@ -106,7 +107,7 @@ notifyOptions log o = do
Nixpkgs Dir: $npDir Nixpkgs Dir: $npDir
----------------------------------|] ----------------------------------|]
updateAll :: Options -> Text -> IO () updateAll :: Text -> RIO Options ()
updateAll o updates = do updateAll o updates = do
log <- getLog o log <- getLog o
log "New run of nixpkgs-update" log "New run of nixpkgs-update"
@ -226,9 +227,10 @@ updatePackageBatch log updateEnv@UpdateEnv {..} mergeBaseOutpathsContext =
assertNotUpdatedOn updateEnv derivationFile "staging-next" assertNotUpdatedOn updateEnv derivationFile "staging-next"
-- Calculate output paths for rebuilds and our merge base -- Calculate output paths for rebuilds and our merge base
mergeBase <- if batchUpdate options mergeBase <-
then Git.checkoutAtMergeBase (branchName updateEnv) if batchUpdate options
else pure "HEAD" then Git.checkoutAtMergeBase (branchName updateEnv)
else pure "HEAD"
let calcOutpaths = calculateOutpaths options let calcOutpaths = calculateOutpaths options
oneHourAgo <- liftIO $ runM $ Time.runIO Time.oneHourAgo oneHourAgo <- liftIO $ runM $ Time.runIO Time.oneHourAgo
mergeBaseOutpathsInfo <- liftIO $ readIORef mergeBaseOutpathsContext mergeBaseOutpathsInfo <- liftIO $ readIORef mergeBaseOutpathsContext
@ -638,11 +640,10 @@ cveReport updateEnv =
doCachix :: MonadIO m => (Text -> m ()) -> UpdateEnv -> Text -> ExceptT Text m Text doCachix :: MonadIO m => (Text -> m ()) -> UpdateEnv -> Text -> ExceptT Text m Text
doCachix log updateEnv resultPath = doCachix log updateEnv resultPath =
let o = options updateEnv let o = options updateEnv
in in if batchUpdate o && "r-ryantm" == (GH.untagName $ githubUser o)
if batchUpdate o && "r-ryantm" == (GH.untagName $ githubUser o) then do
then do return
return [interpolate|
[interpolate|
Either **download from Cachix**: Either **download from Cachix**:
``` ```
nix-store -r $resultPath \ nix-store -r $resultPath \
@ -657,9 +658,9 @@ doCachix log updateEnv resultPath =
Or, **build yourself**: Or, **build yourself**:
|] |]
else do else do
lift $ log "skipping cachix" lift $ log "skipping cachix"
return "Build yourself:" return "Build yourself:"
updatePackage :: updatePackage ::
Options -> Options ->

View File

@ -176,13 +176,13 @@ regDirMode =
directoryMode .|. ownerModes .|. groupModes .|. otherReadMode directoryMode .|. ownerModes .|. groupModes .|. otherReadMode
.|. otherExecuteMode .|. otherExecuteMode
logsDirectory :: MonadIO m => ExceptT Text m FilePath logsDirectory :: MonadIO m => m FilePath
logsDirectory = do logsDirectory = do
dir <- dir <- getEnv "LOGS_DIRECTORY"
noteT "Could not get environment variable LOGS_DIRECTORY" $ noteT "Could not get environment variable LOGS_DIRECTORY" $
MaybeT $ MaybeT $
liftIO $ liftIO $
getEnv "LOGS_DIRECTORY"
dirExists <- liftIO $ doesDirectoryExist dir dirExists <- liftIO $ doesDirectoryExist dir
tryAssert ("LOGS_DIRECTORY " <> T.pack dir <> " does not exist.") dirExists tryAssert ("LOGS_DIRECTORY " <> T.pack dir <> " does not exist.") dirExists
unless unless