mirror of
https://github.com/nmattia/niv.git
synced 2024-11-07 22:36:53 +03:00
Track sources.nix versions
This commit is contained in:
parent
29b4dd4dc3
commit
50134f1aa6
@ -33,6 +33,7 @@ with rec
|
|||||||
"^src/Data/HashMap/Strict$"
|
"^src/Data/HashMap/Strict$"
|
||||||
"^src/Niv$"
|
"^src/Niv$"
|
||||||
"^src/Niv/GitHub$"
|
"^src/Niv/GitHub$"
|
||||||
|
"^src/Niv/Sources$"
|
||||||
"^src/Niv/Update$"
|
"^src/Niv/Update$"
|
||||||
"^src.*.hs$"
|
"^src.*.hs$"
|
||||||
"^README.md$"
|
"^README.md$"
|
||||||
|
@ -36,6 +36,7 @@ dependencies:
|
|||||||
- optparse-applicative
|
- optparse-applicative
|
||||||
- process
|
- process
|
||||||
- profunctors
|
- profunctors
|
||||||
|
- pureMD5
|
||||||
- string-qq
|
- string-qq
|
||||||
- text
|
- text
|
||||||
- unliftio
|
- unliftio
|
||||||
|
@ -1,5 +1,4 @@
|
|||||||
{-# LANGUAGE DerivingStrategies #-}
|
{-# LANGUAGE DerivingStrategies #-}
|
||||||
{-# LANGUAGE TemplateHaskell #-}
|
|
||||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||||
{-# LANGUAGE LambdaCase #-}
|
{-# LANGUAGE LambdaCase #-}
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
@ -13,7 +12,6 @@ import Control.Applicative
|
|||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Data.Aeson ((.=))
|
import Data.Aeson ((.=))
|
||||||
import Data.Char (isSpace)
|
import Data.Char (isSpace)
|
||||||
import Data.FileEmbed (embedFile)
|
|
||||||
import Data.Functor
|
import Data.Functor
|
||||||
import Data.HashMap.Strict.Extended
|
import Data.HashMap.Strict.Extended
|
||||||
import Data.Hashable (Hashable)
|
import Data.Hashable (Hashable)
|
||||||
@ -25,7 +23,7 @@ import Niv.Sources
|
|||||||
import Niv.Update
|
import Niv.Update
|
||||||
import System.Environment (getArgs)
|
import System.Environment (getArgs)
|
||||||
import System.Exit (ExitCode(ExitSuccess))
|
import System.Exit (ExitCode(ExitSuccess))
|
||||||
import System.FilePath ((</>), takeDirectory)
|
import System.FilePath (takeDirectory)
|
||||||
import System.Process (readProcessWithExitCode)
|
import System.Process (readProcessWithExitCode)
|
||||||
import UnliftIO
|
import UnliftIO
|
||||||
import qualified Data.Aeson as Aeson
|
import qualified Data.Aeson as Aeson
|
||||||
@ -33,7 +31,6 @@ import qualified Data.ByteString as B
|
|||||||
import qualified Data.ByteString.Char8 as B8
|
import qualified Data.ByteString.Char8 as B8
|
||||||
import qualified Data.HashMap.Strict as HMS
|
import qualified Data.HashMap.Strict as HMS
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import qualified Data.Text.IO as T
|
|
||||||
import qualified Options.Applicative as Opts
|
import qualified Options.Applicative as Opts
|
||||||
import qualified Options.Applicative.Help.Pretty as Opts
|
import qualified Options.Applicative.Help.Pretty as Opts
|
||||||
import qualified System.Directory as Dir
|
import qualified System.Directory as Dir
|
||||||
@ -482,37 +479,6 @@ shouldUpdateNixSourcesNix content =
|
|||||||
_ -> False
|
_ -> False
|
||||||
_ -> False
|
_ -> False
|
||||||
|
|
||||||
warnIfOutdated :: IO ()
|
|
||||||
warnIfOutdated = do
|
|
||||||
tryAny (B.readFile pathNixSourcesNix) >>= \case
|
|
||||||
Left e -> T.putStrLn $ T.unlines
|
|
||||||
[ "Could not read " <> T.pack pathNixSourcesNix
|
|
||||||
, "Error: " <> tshow e
|
|
||||||
]
|
|
||||||
Right content ->
|
|
||||||
if shouldUpdateNixSourcesNix content
|
|
||||||
then
|
|
||||||
T.putStrLn $ T.unlines
|
|
||||||
[ "WARNING: " <> T.pack pathNixSourcesNix <> " is out of date."
|
|
||||||
, "Please run"
|
|
||||||
, " niv init"
|
|
||||||
, "or add the following line in the " <> T.pack pathNixSourcesNix <> " file:"
|
|
||||||
, " # niv: no_update"
|
|
||||||
]
|
|
||||||
else pure ()
|
|
||||||
|
|
||||||
-- | @nix/sources.nix@
|
|
||||||
pathNixSourcesNix :: FilePath
|
|
||||||
pathNixSourcesNix = "nix" </> "sources.nix"
|
|
||||||
|
|
||||||
-- | Glue code between nix and sources.json
|
|
||||||
initNixSourcesNixContent :: B.ByteString
|
|
||||||
initNixSourcesNixContent = $(embedFile "nix/sources.nix")
|
|
||||||
|
|
||||||
-- | Empty JSON map
|
|
||||||
initNixSourcesJsonContent :: B.ByteString
|
|
||||||
initNixSourcesJsonContent = "{}"
|
|
||||||
|
|
||||||
-- | The IO (real) github update
|
-- | The IO (real) github update
|
||||||
githubUpdate' :: Update () ()
|
githubUpdate' :: Update () ()
|
||||||
githubUpdate' = githubUpdate nixPrefetchURL githubLatestRev githubRepo
|
githubUpdate' = githubUpdate nixPrefetchURL githubLatestRev githubRepo
|
||||||
|
@ -53,6 +53,24 @@ green str =
|
|||||||
ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid ANSI.Green] <>
|
ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid ANSI.Green] <>
|
||||||
str <> ANSI.setSGRCode [ANSI.Reset]
|
str <> ANSI.setSGRCode [ANSI.Reset]
|
||||||
|
|
||||||
|
yellow :: String -> String
|
||||||
|
yellow str =
|
||||||
|
ANSI.setSGRCode [ANSI.SetConsoleIntensity ANSI.BoldIntensity] <>
|
||||||
|
ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid ANSI.Yellow] <>
|
||||||
|
str <> ANSI.setSGRCode [ANSI.Reset]
|
||||||
|
|
||||||
|
tyellow :: T.Text -> T.Text
|
||||||
|
tyellow = dimap T.unpack T.pack yellow
|
||||||
|
|
||||||
|
blue :: String -> String
|
||||||
|
blue str =
|
||||||
|
ANSI.setSGRCode [ANSI.SetConsoleIntensity ANSI.BoldIntensity] <>
|
||||||
|
ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid ANSI.Blue] <>
|
||||||
|
str <> ANSI.setSGRCode [ANSI.Reset]
|
||||||
|
|
||||||
|
tblue :: T.Text -> T.Text
|
||||||
|
tblue = dimap T.unpack T.pack blue
|
||||||
|
|
||||||
red :: String -> String
|
red :: String -> String
|
||||||
red str =
|
red str =
|
||||||
ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid ANSI.Red] <>
|
ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid ANSI.Red] <>
|
||||||
|
@ -1,4 +1,5 @@
|
|||||||
{-# LANGUAGE DerivingStrategies #-}
|
{-# LANGUAGE DerivingStrategies #-}
|
||||||
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
{-# LANGUAGE QuasiQuotes #-}
|
{-# LANGUAGE QuasiQuotes #-}
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||||
@ -7,18 +8,30 @@
|
|||||||
module Niv.Sources where
|
module Niv.Sources where
|
||||||
|
|
||||||
import Data.Aeson (FromJSON, FromJSONKey, ToJSON, ToJSONKey)
|
import Data.Aeson (FromJSON, FromJSONKey, ToJSON, ToJSONKey)
|
||||||
|
import Data.FileEmbed (embedFile)
|
||||||
import Data.Bifunctor (first)
|
import Data.Bifunctor (first)
|
||||||
import Data.Hashable (Hashable)
|
import Data.Hashable (Hashable)
|
||||||
|
import Data.List
|
||||||
import Data.String.QQ (s)
|
import Data.String.QQ (s)
|
||||||
import Niv.GitHub
|
import Niv.GitHub
|
||||||
|
import Niv.Logger
|
||||||
import Niv.Update
|
import Niv.Update
|
||||||
import System.FilePath ((</>))
|
import System.FilePath ((</>))
|
||||||
|
import UnliftIO
|
||||||
import qualified Data.Aeson as Aeson
|
import qualified Data.Aeson as Aeson
|
||||||
import qualified Data.Aeson.Extended as Aeson
|
import qualified Data.Aeson.Extended as Aeson
|
||||||
|
import qualified Data.ByteString as B
|
||||||
|
import qualified Data.ByteString.Lazy.Char8 as BL8
|
||||||
|
import qualified Data.Digest.Pure.MD5 as MD5
|
||||||
import qualified Data.HashMap.Strict as HMS
|
import qualified Data.HashMap.Strict as HMS
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
|
import qualified Data.Text.IO as T
|
||||||
import qualified System.Directory as Dir
|
import qualified System.Directory as Dir
|
||||||
|
|
||||||
|
-------------------------------------------------------------------------------
|
||||||
|
-- sources.json related
|
||||||
|
-------------------------------------------------------------------------------
|
||||||
|
|
||||||
data SourcesError
|
data SourcesError
|
||||||
= SourcesDoesntExist
|
= SourcesDoesntExist
|
||||||
| SourceIsntJSON
|
| SourceIsntJSON
|
||||||
@ -51,7 +64,8 @@ getSourcesEither = do
|
|||||||
mapKeys f = HMS.fromList . map (first f) . HMS.toList
|
mapKeys f = HMS.fromList . map (first f) . HMS.toList
|
||||||
|
|
||||||
getSources :: IO Sources
|
getSources :: IO Sources
|
||||||
getSources =
|
getSources = do
|
||||||
|
warnIfOutdated
|
||||||
getSourcesEither >>= either
|
getSourcesEither >>= either
|
||||||
(\case
|
(\case
|
||||||
SourcesDoesntExist -> abortSourcesDoesntExist
|
SourcesDoesntExist -> abortSourcesDoesntExist
|
||||||
@ -76,9 +90,9 @@ attrsToSpec = PackageSpec . fmap snd
|
|||||||
pathNixSourcesJson :: FilePath
|
pathNixSourcesJson :: FilePath
|
||||||
pathNixSourcesJson = "nix" </> "sources.json"
|
pathNixSourcesJson = "nix" </> "sources.json"
|
||||||
|
|
||||||
-------------------------------------------------------------------------------
|
--
|
||||||
-- ABORT messages
|
-- ABORT messages
|
||||||
-------------------------------------------------------------------------------
|
--
|
||||||
|
|
||||||
abortSourcesDoesntExist :: IO a
|
abortSourcesDoesntExist :: IO a
|
||||||
abortSourcesDoesntExist = abort $ T.unlines [ line1, line2 ]
|
abortSourcesDoesntExist = abort $ T.unlines [ line1, line2 ]
|
||||||
@ -103,3 +117,100 @@ The package specifications in the sources file should be JSON maps from
|
|||||||
attribute name to attribute value, e.g.:
|
attribute name to attribute value, e.g.:
|
||||||
{ "nixpkgs": { "foo": "bar" } }
|
{ "nixpkgs": { "foo": "bar" } }
|
||||||
|]
|
|]
|
||||||
|
|
||||||
|
-------------------------------------------------------------------------------
|
||||||
|
-- sources.nix related
|
||||||
|
-------------------------------------------------------------------------------
|
||||||
|
|
||||||
|
|
||||||
|
-- | All the released versions of nix/sources.nix
|
||||||
|
data SourcesNixVersion
|
||||||
|
= V1
|
||||||
|
| V2
|
||||||
|
| V3
|
||||||
|
| V4
|
||||||
|
| V5
|
||||||
|
| V6
|
||||||
|
| V7
|
||||||
|
| V8
|
||||||
|
| V9
|
||||||
|
| V10
|
||||||
|
deriving stock (Bounded, Enum, Eq)
|
||||||
|
|
||||||
|
-- | A user friendly version
|
||||||
|
sourcesVersionToText :: SourcesNixVersion -> T.Text
|
||||||
|
sourcesVersionToText = \case
|
||||||
|
V1 -> "1"
|
||||||
|
V2 -> "2"
|
||||||
|
V3 -> "3"
|
||||||
|
V4 -> "4"
|
||||||
|
V5 -> "5"
|
||||||
|
V6 -> "6"
|
||||||
|
V7 -> "7"
|
||||||
|
V8 -> "8"
|
||||||
|
V9 -> "9"
|
||||||
|
V10 -> "10"
|
||||||
|
|
||||||
|
latestVersionMD5 :: T.Text
|
||||||
|
latestVersionMD5 = sourcesVersionToMD5 maxBound
|
||||||
|
|
||||||
|
-- | Find a version based on the md5 of the nix/sources.nix
|
||||||
|
md5ToSourcesVersion :: T.Text -> Maybe SourcesNixVersion
|
||||||
|
md5ToSourcesVersion md5 =
|
||||||
|
find (\snv -> sourcesVersionToMD5 snv == md5) [minBound .. maxBound]
|
||||||
|
|
||||||
|
-- | The MD5 sum of a particular version
|
||||||
|
sourcesVersionToMD5 :: SourcesNixVersion -> T.Text
|
||||||
|
sourcesVersionToMD5 = \case
|
||||||
|
V1 -> "a7d3532c70fea66ffa25d6bc7ee49ad5"
|
||||||
|
V2 -> "24cc0719fa744420a04361e23a3598d0"
|
||||||
|
V3 -> "e01ed051e2c416e0fc7355fc72aeee3d"
|
||||||
|
V4 -> "f754fe0e661b61abdcd32cb4062f5014"
|
||||||
|
V5 -> "c34523590ff7dec7bf0689f145df29d1"
|
||||||
|
V6 -> "8143f1db1e209562faf80a998be4929a"
|
||||||
|
V7 -> "00a02cae76d30bbef96f001cabeed96f"
|
||||||
|
V8 -> "e8b860753dd7fa1fd7b805dd836eb607"
|
||||||
|
V9 -> "87149616c1b3b1e5aa73178f91c20b53"
|
||||||
|
V10 -> "d8625c0a03dd935e1c79f46407faa8d3"
|
||||||
|
|
||||||
|
-- | The MD5 sum of ./nix/sources.nix
|
||||||
|
sourcesNixMD5 :: IO T.Text
|
||||||
|
sourcesNixMD5 = T.pack . show . MD5.md5 <$> BL8.readFile pathNixSourcesNix
|
||||||
|
|
||||||
|
-- | @nix/sources.nix@
|
||||||
|
pathNixSourcesNix :: FilePath
|
||||||
|
pathNixSourcesNix = "nix" </> "sources.nix"
|
||||||
|
|
||||||
|
warnIfOutdated :: IO ()
|
||||||
|
warnIfOutdated = do
|
||||||
|
tryAny (BL8.readFile pathNixSourcesNix) >>= \case
|
||||||
|
Left e -> T.putStrLn $ T.unlines -- warn with tsay
|
||||||
|
[ "Could not read " <> T.pack pathNixSourcesNix
|
||||||
|
, "Error: " <> tshow e
|
||||||
|
]
|
||||||
|
Right content -> do
|
||||||
|
case md5ToSourcesVersion (T.pack $ show $ MD5.md5 content) of
|
||||||
|
-- This is a custom version, we don't do anything
|
||||||
|
Nothing -> pure ()
|
||||||
|
Just v
|
||||||
|
-- The file is the latest
|
||||||
|
| v == maxBound -> pure ()
|
||||||
|
| otherwise -> do
|
||||||
|
tsay $ T.unlines
|
||||||
|
[ T.unwords
|
||||||
|
[ tbold $ tblue "INFO:"
|
||||||
|
, "new sources.nix available:"
|
||||||
|
, sourcesVersionToText v, "->", sourcesVersionToText maxBound
|
||||||
|
]
|
||||||
|
, " Please run 'niv init' or add the following line in the " <>
|
||||||
|
T.pack pathNixSourcesNix <> " file:"
|
||||||
|
, " # niv: no_update"
|
||||||
|
]
|
||||||
|
|
||||||
|
-- | Glue code between nix and sources.json
|
||||||
|
initNixSourcesNixContent :: B.ByteString
|
||||||
|
initNixSourcesNixContent = $(embedFile "nix/sources.nix")
|
||||||
|
|
||||||
|
-- | Empty JSON map
|
||||||
|
initNixSourcesJsonContent :: B.ByteString
|
||||||
|
initNixSourcesJsonContent = "{}"
|
||||||
|
13
src/Niv/Sources/Test.hs
Normal file
13
src/Niv/Sources/Test.hs
Normal file
@ -0,0 +1,13 @@
|
|||||||
|
module Niv.Sources.Test where
|
||||||
|
|
||||||
|
import Niv.Sources
|
||||||
|
import Test.Tasty.HUnit ((@=?))
|
||||||
|
import qualified Data.ByteString.Lazy as BL
|
||||||
|
import qualified Data.Digest.Pure.MD5 as MD5
|
||||||
|
import qualified Data.Text as T
|
||||||
|
|
||||||
|
-- | Ensure that the sources.nix we ship is tracked as the latest version
|
||||||
|
test_shippedSourcesNixIsLatest :: IO ()
|
||||||
|
test_shippedSourcesNixIsLatest =
|
||||||
|
latestVersionMD5 @=?
|
||||||
|
(T.pack . show . MD5.md5 . BL.fromStrict $ initNixSourcesNixContent)
|
@ -1,5 +1,6 @@
|
|||||||
module Niv.Test (tests, test) where
|
module Niv.Test (tests, test) where
|
||||||
|
|
||||||
|
import Niv.Sources.Test
|
||||||
import Niv.GitHub.Test
|
import Niv.GitHub.Test
|
||||||
import Niv.Update.Test
|
import Niv.Update.Test
|
||||||
import qualified Test.Tasty as Tasty
|
import qualified Test.Tasty as Tasty
|
||||||
@ -27,4 +28,7 @@ tests = Tasty.testGroup "niv"
|
|||||||
, Tasty.testCase "doesn't override rev" test_githubDoesntOverrideRev
|
, Tasty.testCase "doesn't override rev" test_githubDoesntOverrideRev
|
||||||
, Tasty.testCase "falls back to URL" test_githubURLFallback
|
, Tasty.testCase "falls back to URL" test_githubURLFallback
|
||||||
]
|
]
|
||||||
|
, Tasty.testGroup "sources.nix"
|
||||||
|
[ Tasty.testCase "has latest version" test_shippedSourcesNixIsLatest
|
||||||
|
]
|
||||||
]
|
]
|
||||||
|
Loading…
Reference in New Issue
Block a user