{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Update.Nix.FetchGit
( updatesFromFile
, processFile
) where
import Control.Concurrent.Async (mapConcurrently)
import Control.Error
import Data.Foldable (toList)
import Data.Generics.Uniplate.Data (para)
import Data.Text (Text, pack)
import Nix.Expr
import Update.Nix.FetchGit.Prefetch
import Update.Nix.FetchGit.Types
import Update.Nix.FetchGit.Utils
import Update.Nix.FetchGit.Warning
import Update.Span
import qualified Data.Text.IO
import qualified System.IO
import qualified System.Exit
processFile :: FilePath -> [Text] -> IO ()
processFile filename args = do
t <- Data.Text.IO.readFile filename
updatesFromFile filename args >>= \case
Left ws -> printErrorAndExit ws
Right us ->
case updateSpans us t of
t' | t' /= t -> do
Data.Text.IO.writeFile filename t'
putStrLn $ "Made " ++ (show $ length us) ++ " changes"
_ -> putStrLn "No updates"
where
printErrorAndExit :: Warning -> IO ()
printErrorAndExit e = do
System.IO.hPutStrLn System.IO.stderr (formatWarning e)
System.Exit.exitFailure
updatesFromFile :: FilePath -> [Text] -> IO (Either Warning [SpanUpdate])
updatesFromFile f extraArgs = runExceptT $ do
expr <- ExceptT $ ourParseNixFile f
treeWithArgs <- hoistEither $ exprToFetchTree expr
treeWithLatest <- ExceptT $
sequenceA <$> mapConcurrently (getFetchGitLatestInfo extraArgs) treeWithArgs
pure (fetchTreeToSpanUpdates treeWithLatest)
exprToFetchTree :: NExprLoc -> Either Warning (FetchTree FetchGitArgs)
exprToFetchTree = para $ \e subs -> case e of
AnnE _ (NBinary NApp function (AnnE _ (NSet _rec bindings)))
| extractFuncName function == Just "fetchgit"
|| extractFuncName function == Just "fetchgitPrivate"
-> FetchNode <$> extractFetchGitArgs bindings
AnnE _ (NBinary NApp function (AnnE _ (NSet _rec bindings)))
| extractFuncName function == Just "fetchGit"
-> FetchNode <$> extractFetchGitBuiltinArgs bindings
AnnE _ (NBinary NApp function (AnnE _ (NSet _rec bindings)))
| extractFuncName function == Just "fetchFromGitHub"
-> FetchNode <$> extractFetchFromGitHubArgs bindings
AnnE _ (NBinary NApp function (AnnE _ (NSet _rec bindings)))
| extractFuncName function == Just "fetchFromGitLab"
-> FetchNode <$> extractFetchFromGitLabArgs bindings
AnnE _ (NSet _rec bindings)
-> Node <$> findAttr "version" bindings <*> sequenceA subs
_ -> Node Nothing <$> sequenceA subs
extractFetchGitArgs :: [Binding NExprLoc] -> Either Warning FetchGitArgs
extractFetchGitArgs bindings =
FetchGitArgs <$> (URL <$> (exprText =<< extractAttr "url" bindings))
<*> extractAttr "rev" bindings
<*> (Just <$> extractAttr "sha256" bindings)
extractFetchGitBuiltinArgs :: [Binding NExprLoc] -> Either Warning FetchGitArgs
extractFetchGitBuiltinArgs bindings =
FetchGitArgs <$> (URL <$> (exprText =<< extractAttr "url" bindings))
<*> extractAttr "rev" bindings
<*> pure Nothing
extractFetchFromGitHubArgs :: [Binding NExprLoc] -> Either Warning FetchGitArgs
extractFetchFromGitHubArgs bindings =
FetchGitArgs <$> (GitHub <$> (exprText =<< extractAttr "owner" bindings)
<*> (exprText =<< extractAttr "repo" bindings))
<*> extractAttr "rev" bindings
<*> (Just <$> extractAttr "sha256" bindings)
extractFetchFromGitLabArgs :: [Binding NExprLoc] -> Either Warning FetchGitArgs
extractFetchFromGitLabArgs bindings =
FetchGitArgs <$> (GitLab <$> (exprText =<< extractAttr "owner" bindings)
<*> (exprText =<< extractAttr "repo" bindings))
<*> extractAttr "rev" bindings
<*> (Just <$> extractAttr "sha256" bindings)
getFetchGitLatestInfo :: [Text] -> FetchGitArgs -> IO (Either Warning FetchGitLatestInfo)
getFetchGitLatestInfo extraArgs args = runExceptT $ do
o <- ExceptT (nixPrefetchGit extraArgs (extractUrlString $ repoLocation args))
d <- hoistEither (parseISO8601DateToDay (date o))
pure $ FetchGitLatestInfo args (rev o) (sha256 o) d
fetchTreeToSpanUpdates :: FetchTree FetchGitLatestInfo -> [SpanUpdate]
fetchTreeToSpanUpdates node@(Node _ cs) =
concatMap fetchTreeToSpanUpdates cs ++
toList (maybeUpdateVersion node)
fetchTreeToSpanUpdates (FetchNode f) = catMaybes [Just revUpdate, sha256Update]
where revUpdate = SpanUpdate (exprSpan (revExpr args))
(quoteString (latestRev f))
sha256Update = SpanUpdate <$> (exprSpan <$> sha256Expr args)
<*> Just (quoteString (latestSha256 f))
args = originalInfo f
maybeUpdateVersion :: FetchTree FetchGitLatestInfo -> Maybe SpanUpdate
maybeUpdateVersion node@(Node (Just versionExpr) _) = do
maxDay <- (maximumMay . fmap latestDate . toList) node
pure $ SpanUpdate (exprSpan versionExpr) ((quoteString . pack . show) maxDay)
maybeUpdateVersion _ = Nothing