nix: update eval commands

This commit is contained in:
Ryan Mulligan 2023-01-03 19:53:27 -08:00
parent b294040b32
commit 9f8166a7f9
5 changed files with 58 additions and 198 deletions

View File

@ -1,10 +1,10 @@
cabal-version: 2.2 cabal-version: 2.2
-- This file has been generated from package.yaml by hpack version 0.34.7. -- This file has been generated from package.yaml by hpack version 0.35.0.
-- --
-- see: https://github.com/sol/hpack -- see: https://github.com/sol/hpack
-- --
-- hash: a211130dbcad57cde6ded74551b5390d00263e875e811750d2e3f168e96fcccf -- hash: 94f21d6da342bb311acc23da9681dae7e37fda3ecbf6b623de9880de38785605
name: nixpkgs-update name: nixpkgs-update
version: 0.4.0 version: 0.4.0
@ -175,7 +175,6 @@ test-suite spec
other-modules: other-modules:
CheckSpec CheckSpec
DoctestSpec DoctestSpec
RewriteSpec
UpdateSpec UpdateSpec
UtilsSpec UtilsSpec
hs-source-dirs: hs-source-dirs:

View File

@ -15,16 +15,13 @@ module Nix
getHash, getHash,
getHashFromBuild, getHashFromBuild,
getHomepage, getHomepage,
getHomepageET,
getIsBroken, getIsBroken,
getMaintainers, getMaintainers,
getOldHash,
getPatches, getPatches,
getSrcUrl, getSrcUrl,
hasPatchNamed, hasPatchNamed,
hasUpdateScript, hasUpdateScript,
lookupAttrPath, lookupAttrPath,
nixEvalET,
numberOfFetchers, numberOfFetchers,
numberOfHashes, numberOfHashes,
resultLink, resultLink,
@ -42,10 +39,7 @@ import qualified Data.Text.Lazy.Encoding as TL
import qualified Git import qualified Git
import Language.Haskell.TH.Env (envQ) import Language.Haskell.TH.Env (envQ)
import OurPrelude import OurPrelude
import qualified Polysemy.Error as Error
import qualified System.Process.Typed as TP import qualified System.Process.Typed as TP
import qualified Process
import qualified Process as P
import System.Exit() import System.Exit()
import Utils (UpdateEnv (..), nixBuildOptions, nixCommonOptions, srcOrMain) import Utils (UpdateEnv (..), nixBuildOptions, nixCommonOptions, srcOrMain)
import Prelude hiding (log) import Prelude hiding (log)
@ -65,28 +59,30 @@ rawOpt :: Raw -> [String]
rawOpt Raw = ["--raw"] rawOpt Raw = ["--raw"]
rawOpt NoRaw = [] rawOpt NoRaw = []
nixEvalSem :: nixEvalApply ::
Members '[P.Process, Error Text] r => MonadIO m =>
EvalOptions -> Text ->
Text -> Text ->
Sem r (Text, Text) ExceptT Text m Text
nixEvalSem (EvalOptions raw (Env env)) expr = nixEvalApply applyFunc attrPath =
(\(stdout, stderr) -> (T.strip stdout, T.strip stderr))
<$> ourReadProcess_Sem
(setEnv env (proc (binPath <> "/nix") (["eval", "-f", "."] <> rawOpt raw <> [T.unpack expr])))
nixEvalET :: MonadIO m => EvalOptions -> Text -> ExceptT Text m Text
nixEvalET (EvalOptions raw (Env env)) expr =
ourReadProcess_ ourReadProcess_
(setEnv env (proc (binPath <> "/nix") (["eval", "-f", "."] <> rawOpt raw <> [T.unpack expr]))) (proc (binPath <> "/nix") (["eval", ".#" <> T.unpack attrPath, "--apply", T.unpack applyFunc]))
& fmapRT (fst >>> T.strip)
nixEvalExpr ::
MonadIO m =>
Text ->
ExceptT Text m Text
nixEvalExpr expr =
ourReadProcess_
(proc (binPath <> "/nix") (["eval", "--expr", T.unpack expr]))
& fmapRT (fst >>> T.strip) & fmapRT (fst >>> T.strip)
-- Error if the "new version" is actually newer according to nix -- Error if the "new version" is actually newer according to nix
assertNewerVersion :: MonadIO m => UpdateEnv -> ExceptT Text m () assertNewerVersion :: MonadIO m => UpdateEnv -> ExceptT Text m ()
assertNewerVersion updateEnv = do assertNewerVersion updateEnv = do
versionComparison <- versionComparison <-
nixEvalET nixEvalExpr
(EvalOptions NoRaw (Env []))
( "(builtins.compareVersions \"" ( "(builtins.compareVersions \""
<> newVersion updateEnv <> newVersion updateEnv
<> "\" \"" <> "\" \""
@ -123,10 +119,8 @@ lookupAttrPath updateEnv =
& fmapRT (fst >>> T.lines >>> head >>> T.words >>> head)) & fmapRT (fst >>> T.lines >>> head >>> T.words >>> head))
<|> <|>
-- if that fails, check by attrpath -- if that fails, check by attrpath
(nixEvalET (getAttr "name" (packageName updateEnv))
(EvalOptions Raw (Env [])) & fmapRT (const (packageName updateEnv))
("pkgs." <> packageName updateEnv)
& fmapRT (const (packageName updateEnv)))
getDerivationFile :: MonadIO m => Text -> ExceptT Text m Text getDerivationFile :: MonadIO m => Text -> ExceptT Text m Text
getDerivationFile attrPath = do getDerivationFile attrPath = do
@ -137,28 +131,15 @@ getDerivationFile attrPath = do
-- Get an attribute that can be evaluated off a derivation, as in: -- Get an attribute that can be evaluated off a derivation, as in:
-- getAttr "cargoSha256" "ripgrep" -> 0lwz661rbm7kwkd6mallxym1pz8ynda5f03ynjfd16vrazy2dj21 -- getAttr "cargoSha256" "ripgrep" -> 0lwz661rbm7kwkd6mallxym1pz8ynda5f03ynjfd16vrazy2dj21
getAttr :: MonadIO m => Raw -> Text -> Text -> ExceptT Text m Text getAttr :: MonadIO m => Text -> Text -> ExceptT Text m Text
getAttr raw attr = getAttr attr = srcOrMain (nixEvalApply ("p: p."<> attr))
srcOrMain
(\attrPath -> nixEvalET (EvalOptions raw (Env [])) (attrPath <> "." <> attr))
getHash :: MonadIO m => Text -> ExceptT Text m Text getHash :: MonadIO m => Text -> ExceptT Text m Text
getHash = getHash = getAttr "drvAttrs.outputHash"
srcOrMain
(\attrPath -> nixEvalET (EvalOptions Raw (Env [])) ("pkgs." <> attrPath <> ".drvAttrs.outputHash"))
getOldHash :: MonadIO m => Text -> ExceptT Text m Text
getOldHash attrPath =
getHash attrPath
getMaintainers :: MonadIO m => Text -> ExceptT Text m Text getMaintainers :: MonadIO m => Text -> ExceptT Text m Text
getMaintainers attrPath = getMaintainers =
nixEvalET nixEvalApply "p: let gh = m : m.github or \"\"; nonempty = s: s != \"\"; addAt = s: \"@\"+s; in builtins.concatStringsSep \" \" (map addAt (builtins.filter nonempty (map gh p.meta.maintainers or []))"
(EvalOptions Raw (Env []))
( "(let pkgs = import ./. {}; gh = m : m.github or \"\"; nonempty = s: s != \"\"; addAt = s: \"@\"+s; in builtins.concatStringsSep \" \" (map addAt (builtins.filter nonempty (map gh pkgs."
<> attrPath
<> ".meta.maintainers or []))))"
)
readNixBool :: MonadIO m => ExceptT Text m Text -> ExceptT Text m Bool readNixBool :: MonadIO m => ExceptT Text m Text -> ExceptT Text m Bool
readNixBool t = do readNixBool t = do
@ -170,65 +151,21 @@ readNixBool t = do
getIsBroken :: MonadIO m => Text -> ExceptT Text m Bool getIsBroken :: MonadIO m => Text -> ExceptT Text m Bool
getIsBroken attrPath = getIsBroken attrPath =
nixEvalET getAttr "meta.broken" attrPath
(EvalOptions NoRaw (Env []))
( "(let pkgs = import ./. {}; in pkgs."
<> attrPath
<> ".meta.broken or false)"
)
& readNixBool & readNixBool
getChangelog :: MonadIO m => Text -> ExceptT Text m Text getChangelog :: MonadIO m => Text -> ExceptT Text m Text
getChangelog attrPath = getChangelog = nixEvalApply "p: p.meta.changelog or \"\""
nixEvalET
(EvalOptions NoRaw (Env []))
( "(let pkgs = import ./. {}; in pkgs."
<> attrPath
<> ".meta.changelog or \"\")"
)
getDescription :: MonadIO m => Text -> ExceptT Text m Text getDescription :: MonadIO m => Text -> ExceptT Text m Text
getDescription attrPath = getDescription = nixEvalApply "p: p.meta.description or \"\""
nixEvalET
(EvalOptions NoRaw (Env []))
( "(let pkgs = import ./. {}; in pkgs."
<> attrPath
<> ".meta.description or \"\")"
)
getHomepage :: getHomepage :: MonadIO m => Text -> ExceptT Text m Text
Members '[P.Process, Error Text] r => getHomepage = nixEvalApply "p: p.meta.homepage or \"\""
Text ->
Sem r Text
getHomepage attrPath =
fst <$> nixEvalSem
(EvalOptions NoRaw (Env []))
( "(let pkgs = import ./. {}; in pkgs."
<> attrPath
<> ".meta.homepage or \"\")"
)
getHomepageET :: MonadIO m => Text -> ExceptT Text m Text
getHomepageET attrPath =
ExceptT
. liftIO
. runFinal
. embedToFinal
. Error.runError
. Process.runIO
$ getHomepage attrPath
getSrcUrl :: MonadIO m => Text -> ExceptT Text m Text getSrcUrl :: MonadIO m => Text -> ExceptT Text m Text
getSrcUrl = getSrcUrl = srcOrMain
srcOrMain (nixEvalApply "p: builtins.elemAt p.drvAttrs.urls 0")
( \attrPath ->
nixEvalET
(EvalOptions Raw (Env []))
( "(let pkgs = import ./. {}; in builtins.elemAt pkgs."
<> attrPath
<> ".drvAttrs.urls 0)"
)
)
buildCmd :: Text -> ProcessConfig () () () buildCmd :: Text -> ProcessConfig () () ()
buildCmd attrPath = buildCmd attrPath =
@ -323,13 +260,8 @@ version :: MonadIO m => ExceptT Text m Text
version = ourReadProcessInterleaved_ (proc (binPath <> "/nix") ["--version"]) version = ourReadProcessInterleaved_ (proc (binPath <> "/nix") ["--version"])
getPatches :: MonadIO m => Text -> ExceptT Text m Text getPatches :: MonadIO m => Text -> ExceptT Text m Text
getPatches attrPath = getPatches =
nixEvalET nixEvalApply "p: map (patch: patch.name) p.patches"
(EvalOptions NoRaw (Env []))
( "(let pkgs = import ./. {}; in (map (p: p.name) pkgs."
<> attrPath
<> ".patches))"
)
hasPatchNamed :: MonadIO m => Text -> Text -> ExceptT Text m Bool hasPatchNamed :: MonadIO m => Text -> Text -> ExceptT Text m Bool
hasPatchNamed attrPath name = do hasPatchNamed attrPath name = do
@ -337,17 +269,10 @@ hasPatchNamed attrPath name = do
return $ name `T.isInfixOf` ps return $ name `T.isInfixOf` ps
hasUpdateScript :: MonadIO m => Text -> ExceptT Text m Bool hasUpdateScript :: MonadIO m => Text -> ExceptT Text m Bool
hasUpdateScript attrPath = do hasUpdateScript attrPath= do
result <- nixEvalApply
nixEvalET "p: builtins.hasAttr \"updateScript\" p" attrPath
(EvalOptions NoRaw (Env [])) & readNixBool
( "(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 :: MonadIO m => Text -> ExceptT Text m (ExitCode, Text)
runUpdateScript attrPath = do runUpdateScript attrPath = do

View File

@ -8,7 +8,6 @@ module Rewrite
runAll, runAll,
golangModuleVersion, golangModuleVersion,
quotedUrls, quotedUrls,
quotedUrlsET,
rustCrateVersion, rustCrateVersion,
version, version,
redirectedUrls, redirectedUrls,
@ -24,15 +23,9 @@ import qualified Network.HTTP.Client as HTTP
import Network.HTTP.Types.Status (statusCode) import Network.HTTP.Types.Status (statusCode)
import qualified Nix import qualified Nix
import OurPrelude import OurPrelude
import qualified Polysemy.Error as Error
import Polysemy.Output (Output, output)
import qualified Process
import System.Exit() import System.Exit()
import Utils (UpdateEnv (..)) import Utils (UpdateEnv (..))
import qualified Utils import qualified Utils (stripQuotes)
( runLog,
stripQuotes,
)
import Prelude hiding (log) import Prelude hiding (log)
{- {-
@ -69,7 +62,7 @@ plan =
("rustCrateVersion", rustCrateVersion), ("rustCrateVersion", rustCrateVersion),
("golangModuleVersion", golangModuleVersion), ("golangModuleVersion", golangModuleVersion),
("updateScript", updateScript), ("updateScript", updateScript),
("", quotedUrlsET) -- Don't change the logger ("", quotedUrls) -- Don't change the logger
--("redirectedUrl", Rewrite.redirectedUrls) --("redirectedUrl", Rewrite.redirectedUrls)
] ]
@ -103,47 +96,32 @@ version log args@Args {..} = do
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Rewrite meta.homepage (and eventually other URLs) to be quoted if not -- Rewrite meta.homepage (and eventually other URLs) to be quoted if not
-- already, as per https://github.com/NixOS/rfcs/pull/45 -- already, as per https://github.com/NixOS/rfcs/pull/45
quotedUrls :: quotedUrls :: (Text -> IO ()) -> Args -> ExceptT Text IO (Maybe Text)
Members '[Process.Process, File.File, Error Text, Output Text] r => quotedUrls log Args {..} = do
Args -> lift $ log "[quotedUrls]"
Sem r (Maybe Text)
quotedUrls Args {..} = do
output "[quotedUrls]"
homepage <- Nix.getHomepage attrPath homepage <- Nix.getHomepage attrPath
stripped <- case Utils.stripQuotes homepage of stripped <- case Utils.stripQuotes homepage of
Nothing -> throw "Could not strip url! This should never happen!" Nothing -> throwE "Could not strip url! This should never happen!"
Just x -> pure x Just x -> pure x
let goodHomepage = "homepage = " <> homepage <> ";" let goodHomepage = "homepage = " <> homepage <> ";"
let replacer = \target -> File.replace target goodHomepage derivationFile let replacer = \target -> File.replaceIO target goodHomepage derivationFile
urlReplaced1 <- replacer ("homepage = " <> stripped <> ";") urlReplaced1 <- replacer ("homepage = " <> stripped <> ";")
urlReplaced2 <- replacer ("homepage = " <> stripped <> " ;") urlReplaced2 <- replacer ("homepage = " <> stripped <> " ;")
urlReplaced3 <- replacer ("homepage =" <> stripped <> ";") urlReplaced3 <- replacer ("homepage =" <> stripped <> ";")
urlReplaced4 <- replacer ("homepage =" <> stripped <> "; ") urlReplaced4 <- replacer ("homepage =" <> stripped <> "; ")
if urlReplaced1 || urlReplaced2 || urlReplaced3 || urlReplaced4 if urlReplaced1 || urlReplaced2 || urlReplaced3 || urlReplaced4
then do then do
output "[quotedUrls]: added quotes to meta.homepage" lift $ log "[quotedUrls]: added quotes to meta.homepage"
return $ Just "Quoted meta.homepage for [RFC 45](https://github.com/NixOS/rfcs/pull/45)" return $ Just "Quoted meta.homepage for [RFC 45](https://github.com/NixOS/rfcs/pull/45)"
else do else do
output "[quotedUrls] nothing found to replace" lift $ log "[quotedUrls] nothing found to replace"
return Nothing return Nothing
quotedUrlsET :: MonadIO m => (Text -> IO ()) -> Args -> ExceptT Text m (Maybe Text)
quotedUrlsET log rwArgs =
ExceptT $
liftIO
. runFinal
. embedToFinal
. Error.runError
. Process.runIO
. File.runIO
. Utils.runLog log
$ quotedUrls rwArgs
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Redirect homepage when moved. -- Redirect homepage when moved.
redirectedUrls :: MonadIO m => (Text -> m ()) -> Args -> ExceptT Text m (Maybe Text) redirectedUrls :: MonadIO m => (Text -> m ()) -> Args -> ExceptT Text m (Maybe Text)
redirectedUrls log Args {..} = do redirectedUrls log Args {..} = do
unstripped <- Nix.getHomepageET attrPath unstripped <- Nix.getHomepage attrPath
homepage <- case Utils.stripQuotes unstripped of homepage <- case Utils.stripQuotes unstripped of
Nothing -> throwE "Could not strip homepage! This should never happen!" Nothing -> throwE "Could not strip homepage! This should never happen!"
Just x -> pure x Just x -> pure x
@ -191,7 +169,7 @@ rustCrateVersion log args@Args {..} = do
-- This starts the same way `version` does, minus the assert -- This starts the same way `version` does, minus the assert
srcVersionFix args srcVersionFix args
-- But then from there we need to do this a second time for the cargoSha256! -- But then from there we need to do this a second time for the cargoSha256!
oldCargoSha256 <- Nix.getAttr Nix.Raw "cargoSha256" attrPath oldCargoSha256 <- Nix.getAttr "cargoSha256" attrPath
_ <- lift $ File.replaceIO oldCargoSha256 Nix.fakeHash derivationFile _ <- lift $ File.replaceIO oldCargoSha256 Nix.fakeHash derivationFile
newCargoSha256 <- Nix.getHashFromBuild attrPath newCargoSha256 <- Nix.getHashFromBuild attrPath
when (oldCargoSha256 == newCargoSha256) $ throwE "cargoSha256 hashes equal; no update necessary" when (oldCargoSha256 == newCargoSha256) $ throwE "cargoSha256 hashes equal; no update necessary"
@ -220,7 +198,7 @@ golangModuleVersion log args@Args {..} = do
srcVersionFix args srcVersionFix args
-- But then from there we need to do this a second time for the vendorSha256! -- 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 -- 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) oldVendorSha256 <- (Nix.getAttr "vendorSha256" attrPath <|> Nix.getAttr "vendorSha256" attrPath)
lift . log $ "Found old vendorSha256 = " <> oldVendorSha256 lift . log $ "Found old vendorSha256 = " <> oldVendorSha256
original <- liftIO $ T.readFile derivationFile original <- liftIO $ T.readFile derivationFile
_ <- lift $ File.replaceIO ("\"" <> oldVendorSha256 <> "\"") "null" derivationFile _ <- lift $ File.replaceIO ("\"" <> oldVendorSha256 <> "\"") "null" derivationFile
@ -265,7 +243,7 @@ updateScript log Args {..} = do
srcVersionFix :: MonadIO m => Args -> ExceptT Text m () srcVersionFix :: MonadIO m => Args -> ExceptT Text m ()
srcVersionFix Args {..} = do srcVersionFix Args {..} = do
let UpdateEnv {..} = updateEnv let UpdateEnv {..} = updateEnv
oldHash <- Nix.getOldHash attrPath oldHash <- Nix.getHash attrPath
_ <- lift $ File.replaceIO oldVersion newVersion derivationFile _ <- lift $ File.replaceIO oldVersion newVersion derivationFile
_ <- lift $ File.replaceIO oldHash Nix.fakeHash derivationFile _ <- lift $ File.replaceIO oldHash Nix.fakeHash derivationFile
newHash <- Nix.getHashFromBuild attrPath newHash <- Nix.getHashFromBuild attrPath

View File

@ -310,10 +310,10 @@ updateAttrPath log mergeBase updateEnv@UpdateEnv {..} attrPath = do
-- Get the original values for diffing purposes -- Get the original values for diffing purposes
derivationContents <- liftIO $ T.readFile $ T.unpack derivationFile derivationContents <- liftIO $ T.readFile $ T.unpack derivationFile
oldHash <- Nix.getOldHash attrPath <|> pure "" oldHash <- Nix.getHash attrPath <|> pure ""
oldSrcUrl <- Nix.getSrcUrl attrPath <|> pure "" oldSrcUrl <- Nix.getSrcUrl attrPath <|> pure ""
oldRev <- Nix.getAttr Nix.Raw "rev" attrPath <|> pure "" oldRev <- Nix.getAttr "rev" attrPath <|> pure ""
oldVerMay <- rightMay `fmapRT` (lift $ runExceptT $ Nix.getAttr Nix.Raw "version" attrPath) oldVerMay <- rightMay `fmapRT` (lift $ runExceptT $ Nix.getAttr "version" attrPath)
tryAssert tryAssert
"The derivation has no 'version' attribute, so do not know how to figure out the version while doing an updateScript update" "The derivation has no 'version' attribute, so do not know how to figure out the version while doing an updateScript update"
@ -340,8 +340,8 @@ updateAttrPath log mergeBase updateEnv@UpdateEnv {..} attrPath = do
updatedDerivationContents <- liftIO $ T.readFile $ T.unpack derivationFile updatedDerivationContents <- liftIO $ T.readFile $ T.unpack derivationFile
newSrcUrl <- Nix.getSrcUrl attrPath <|> pure "" newSrcUrl <- Nix.getSrcUrl attrPath <|> pure ""
newHash <- Nix.getHash attrPath <|> pure "" newHash <- Nix.getHash attrPath <|> pure ""
newRev <- Nix.getAttr Nix.Raw "rev" attrPath <|> pure "" newRev <- Nix.getAttr "rev" attrPath <|> pure ""
newVerMay <- rightMay `fmapRT` (lift $ runExceptT $ Nix.getAttr Nix.Raw "version" attrPath) newVerMay <- rightMay `fmapRT` (lift $ runExceptT $ Nix.getAttr "version" attrPath)
tryAssert tryAssert
"The derivation has no 'version' attribute, so do not know how to figure out the version while doing an updateScript update" "The derivation has no 'version' attribute, so do not know how to figure out the version while doing an updateScript update"
@ -429,7 +429,7 @@ publishPackage log updateEnv oldSrcUrl newSrcUrl attrPath result opReport prBase
Right () -> lift $ Check.result updateEnv (T.unpack result) Right () -> lift $ Check.result updateEnv (T.unpack result)
Left msg -> pure msg Left msg -> pure msg
metaDescription <- Nix.getDescription attrPath <|> return T.empty metaDescription <- Nix.getDescription attrPath <|> return T.empty
metaHomepage <- Nix.getHomepageET attrPath <|> return T.empty metaHomepage <- Nix.getHomepage attrPath <|> return T.empty
metaChangelog <- Nix.getChangelog attrPath <|> return T.empty metaChangelog <- Nix.getChangelog attrPath <|> return T.empty
cveRep <- liftIO $ cveReport updateEnv cveRep <- liftIO $ cveReport updateEnv
releaseUrl <- GH.releaseUrl updateEnv newSrcUrl <|> return "" releaseUrl <- GH.releaseUrl updateEnv newSrcUrl <|> return ""

View File

@ -1,42 +0,0 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module RewriteSpec where
import qualified Data.Text as T
import qualified Data.Text.IO as T
import qualified File
import OurPrelude
import qualified Polysemy.Error as Error
import qualified Polysemy.Output as Output
import qualified Process
import qualified Rewrite
import Test.Hspec
import qualified Utils
main :: IO ()
main = hspec spec
spec :: Spec
spec = do
describe "Rewrite.quotedUrls" 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 "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 False
(logs, (newContents, result)) <-
( runFinal
. embedToFinal
. Output.runOutputList
. File.runPure [nixQuotedHomepageBad]
. Process.runPure ["\"http://troglobit.com/project/inadyn/\""]
. Error.errorToIOFinal
$ Rewrite.quotedUrls rwArgs
)
T.putStrLn $ T.unlines logs
head logs `shouldBe` "[quotedUrls]"
result `shouldBe` Right (Just "Quoted meta.homepage for [RFC 45](https://github.com/NixOS/rfcs/pull/45)")
head newContents `shouldBe` nixQuotedHomepageGood