{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
module Update.Nix.FetchGit.Utils
( RepoLocation(..)
, ourParseNixFile
, extractUrlString
, quoteString
, extractFuncName
, extractAttr
, findAttr
, matchAttr
, exprText
, exprSpan
, parseISO8601DateToDay
, formatWarning
) where
import Data.Maybe ( catMaybes )
import Data.List.NonEmpty as NE
import Data.Text ( Text
, unpack
, splitOn
)
import Data.Time ( parseTimeM
, defaultTimeLocale
)
import Nix.Parser ( parseNixFileLoc
, Result(..)
)
import Nix.Reduce
import Nix.Expr hiding ( SourcePos )
import Update.Nix.FetchGit.Types
import Update.Nix.FetchGit.Warning
import Update.Span
ourParseNixFile :: FilePath -> IO (Either Warning NExprLoc)
ourParseNixFile f =
parseNixFileLoc f >>= \case
Failure parseError -> pure $ Left (CouldNotParseInput parseError)
Success expr -> pure <$> reduceExpr Nothing expr
extractUrlString :: RepoLocation -> Text
extractUrlString = \case
URL u -> u
GitHub o r -> "https://github.com/" <> o <> "/" <> r <> ".git"
GitLab o r -> "https://gitlab.com/" <> o <> "/" <> r <> ".git"
quoteString :: Text -> Text
quoteString t = "\"" <> t <> "\""
exprText :: NExprLoc -> Either Warning Text
exprText = \case
(AnnE _ (NStr (DoubleQuoted [Plain t]))) -> pure t
e -> Left (NotAString e)
exprSpan :: NExprLoc -> SrcSpan
exprSpan (AnnE s _) = s
exprSpan _ = error "unreachable"
extractFuncName :: NExprLoc -> Maybe Text
extractFuncName (AnnE _ (NSym name)) = Just name
extractFuncName (AnnE _ (NSelect _ (NE.last -> StaticKey name) _)) = Just name
extractFuncName _ = Nothing
extractAttr :: Text -> [Binding a] -> Either Warning a
extractAttr name bs = case catMaybes (matchAttr name <$> bs) of
[x] -> pure x
[] -> Left (MissingAttr name)
_ -> Left (DuplicateAttrs name)
findAttr :: Text -> [Binding a] -> Either Warning (Maybe a)
findAttr name bs = case catMaybes (matchAttr name <$> bs) of
[x] -> pure (Just x)
[] -> pure Nothing
_ -> Left (DuplicateAttrs name)
matchAttr :: Text -> Binding a -> Maybe a
matchAttr t = \case
NamedVar (StaticKey t' :|[]) x _ | t == t' -> Just x
NamedVar _ _ _ -> Nothing
Inherit _ _ _ -> Nothing
parseISO8601DateToDay :: Text -> Either Warning Day
parseISO8601DateToDay t =
let justDate = (unpack . Prelude.head . splitOn "T") t in
case parseTimeM False defaultTimeLocale "%Y-%m-%d" justDate of
Nothing -> Left $ InvalidDateString t
Just day -> pure day
formatWarning :: Warning -> String
formatWarning (CouldNotParseInput doc) = show doc
formatWarning (MissingAttr attrName) =
"Error: The \"" <> unpack attrName <> "\" attribute is missing."
formatWarning (DuplicateAttrs attrName) =
"Error: The \"" <> unpack attrName <> "\" attribute appears twice in a set."
formatWarning (NotAString expr) =
"Error: The expression at "
<> (prettyPrintSourcePos . spanBegin . exprSpan) expr
<> " is not a string literal."
formatWarning (NixPrefetchGitFailed exitCode errorOutput) =
"Error: nix-prefetch-git failed with exit code " <> show exitCode
<> " and error output:\n" <> unpack errorOutput
formatWarning (InvalidPrefetchGitOutput output) =
"Error: Output from nix-prefetch-git is invalid:\n" <> show output
formatWarning (InvalidDateString text) =
"Error: Date string is invalid: " <> show text