1
1
mirror of https://github.com/nmattia/niv.git synced 2024-11-07 22:36:53 +03:00

Merge pull request #139 from nmattia/nm-light-refactor

Clean up and refactor
This commit is contained in:
Nicolas Mattia 2019-11-10 16:11:07 +01:00 committed by GitHub
commit 6da5c19aa2
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
2 changed files with 58 additions and 45 deletions

View File

@ -251,10 +251,10 @@ Available options:
``` ```
Examples: Examples:
niv update niv update # update all packages
niv update nixpkgs niv update nixpkgs # update nixpkgs
niv update my-package -v beta-0.2 niv update my-package -v beta-0.2 # update my-package to version "beta-0.2"
Usage: niv update [PACKAGE] ([-a|--attribute KEY=VAL] | [-b|--branch BRANCH] | Usage: niv update [PACKAGE] ([-a|--attribute KEY=VAL] | [-b|--branch BRANCH] |
[-o|--owner OWNER] | [-r|--repo REPO] | [-v|--version VERSION] [-o|--owner OWNER] | [-r|--repo REPO] | [-v|--version VERSION]

View File

@ -12,6 +12,7 @@ module Niv.Cli where
import Control.Applicative import Control.Applicative
import Control.Monad import Control.Monad
import Data.Aeson (FromJSON, FromJSONKey, ToJSON, ToJSONKey, (.=)) import Data.Aeson (FromJSON, FromJSONKey, ToJSON, ToJSONKey, (.=))
import Data.Bifunctor (first)
import Data.Char (isSpace) import Data.Char (isSpace)
import Data.FileEmbed (embedFile) import Data.FileEmbed (embedFile)
import Data.Hashable (Hashable) import Data.Hashable (Hashable)
@ -71,24 +72,41 @@ newtype Sources = Sources
{ unSources :: HMS.HashMap PackageName PackageSpec } { unSources :: HMS.HashMap PackageName PackageSpec }
deriving newtype (FromJSON, ToJSON) deriving newtype (FromJSON, ToJSON)
getSources :: IO Sources data SourcesError
getSources = do = SourcesDoesntExist
exists <- Dir.doesFileExist pathNixSourcesJson | SourceIsntJSON
unless exists abortSourcesDoesntExist | SpecIsntAMap
warnIfOutdated getSourcesEither :: IO (Either SourcesError Sources)
-- TODO: if doesn't exist: run niv init getSourcesEither = do
say $ "Reading sources file" Dir.doesFileExist pathNixSourcesJson >>= \case
decodeFileStrict pathNixSourcesJson >>= \case False -> pure $ Left SourcesDoesntExist
Just (Aeson.Object obj) -> True ->
fmap (Sources . mconcat) $ decodeFileStrict pathNixSourcesJson >>= \case
forM (HMS.toList obj) $ \(k, v) -> Just value -> case valueToSources value of
case v of Nothing -> pure $ Left SpecIsntAMap
Aeson.Object v' -> Just srcs -> pure $ Right srcs
pure $ HMS.singleton (PackageName k) (PackageSpec v') Nothing -> pure $ Left SourceIsntJSON
_ -> abortAttributeIsntAMap where
Just _ -> abortSourcesIsntAMap valueToSources :: Aeson.Value -> Maybe Sources
Nothing -> abortSourcesIsntJSON valueToSources = \case
Aeson.Object obj -> fmap (Sources . mapKeys PackageName) $ traverse
(\case
Aeson.Object obj' -> Just (PackageSpec obj')
_ -> Nothing
) obj
_ -> Nothing
mapKeys :: (Eq k2, Hashable k2) => (k1 -> k2) -> HMS.HashMap k1 v -> HMS.HashMap k2 v
mapKeys f = HMS.fromList . map (first f) . HMS.toList
getSources :: IO Sources
getSources =
getSourcesEither >>= either
(\case
SourcesDoesntExist -> abortSourcesDoesntExist
SourceIsntJSON -> abortSourcesIsntJSON
SpecIsntAMap -> abortSpecIsntAMap
) pure
setSources :: Sources -> IO () setSources :: Sources -> IO ()
setSources sources = encodeFile pathNixSourcesJson sources setSources sources = encodeFile pathNixSourcesJson sources
@ -293,31 +311,25 @@ parseCmdShow =
cmdShow :: Maybe PackageName -> IO () cmdShow :: Maybe PackageName -> IO ()
cmdShow = \case cmdShow = \case
Just packageName -> do Just packageName -> do
tsay $ "Showing package " <> unPackageName packageName
sources <- unSources <$> getSources sources <- unSources <$> getSources
case HMS.lookup packageName sources of case HMS.lookup packageName sources of
Just (PackageSpec spec) -> do Just pspec -> showPackage packageName pspec
forM_ (HMS.toList spec) $ \(attrName, attrValValue) -> do
let attrValue = case attrValValue of
Aeson.String str -> str
_ -> "<barabajagal>"
tsay $ " " <> attrName <> ": " <> attrValue
Nothing -> abortCannotShowNoSuchPackage packageName Nothing -> abortCannotShowNoSuchPackage packageName
Nothing -> do Nothing -> do
say $ "Showing sources file"
sources <- unSources <$> getSources sources <- unSources <$> getSources
forWithKeyM_ sources $ showPackage
showPackage :: PackageName -> PackageSpec -> IO ()
showPackage (PackageName pname) (PackageSpec spec) = do
tsay $ tbold pname
forM_ (HMS.toList spec) $ \(attrName, attrValValue) -> do
let attrValue = case attrValValue of
Aeson.String str -> str
_ -> tfaint "<barabajagal>"
tsay $ " " <> attrName <> ": " <> attrValue
forWithKeyM_ sources $ \key (PackageSpec spec) -> do
tsay $ "Showing " <> tbold (unPackageName key)
forM_ (HMS.toList spec) $ \(attrName, attrValValue) -> do
let attrValue = case attrValValue of
Aeson.String str -> str
_ -> tfaint "<barabajagal>"
tsay $ " " <> attrName <> ": " <> attrValue
------------------------------------------------------------------------------- -------------------------------------------------------------------------------
-- UPDATE -- UPDATE
@ -332,12 +344,14 @@ parseCmdUpdate =
desc = desc =
[ Opts.fullDesc [ Opts.fullDesc
, Opts.progDesc "Update dependencies" , Opts.progDesc "Update dependencies"
, Opts.headerDoc $ Just $ , Opts.headerDoc $ Just $ Opts.nest 2 $
"Examples:" Opts.<$$> "Examples:" Opts.<$$>
"" Opts.<$$> "" Opts.<$$>
" niv update" Opts.<$$> Opts.vcat
" niv update nixpkgs" Opts.<$$> [ Opts.fill 30 "niv update" Opts.<+> "# update all packages",
" niv update my-package -v beta-0.2" Opts.fill 30 "niv update nixpkgs" Opts.<+> "# update nixpkgs",
Opts.fill 30 "niv update my-package -v beta-0.2" Opts.<+> "# update my-package to version \"beta-0.2\""
]
] ]
specToFreeAttrs :: PackageSpec -> Attrs specToFreeAttrs :: PackageSpec -> Attrs
@ -346,7 +360,6 @@ specToFreeAttrs = fmap (Free,) . unPackageSpec
specToLockedAttrs :: PackageSpec -> Attrs specToLockedAttrs :: PackageSpec -> Attrs
specToLockedAttrs = fmap (Locked,) . unPackageSpec specToLockedAttrs = fmap (Locked,) . unPackageSpec
-- TODO: sexy logging + concurrent updates
cmdUpdate :: Maybe (PackageName, PackageSpec) -> IO () cmdUpdate :: Maybe (PackageName, PackageSpec) -> IO ()
cmdUpdate = \case cmdUpdate = \case
Just (packageName, cliSpec) -> Just (packageName, cliSpec) ->
@ -621,8 +634,8 @@ specification, e.g.:
{ ... } { ... }
|] |]
abortAttributeIsntAMap :: IO a abortSpecIsntAMap :: IO a
abortAttributeIsntAMap = abort $ T.unlines [ line1, line2 ] abortSpecIsntAMap = abort $ T.unlines [ line1, line2 ]
where where
line1 = "Cannot use " <> T.pack pathNixSourcesJson line1 = "Cannot use " <> T.pack pathNixSourcesJson
line2 = [s| line2 = [s|