{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
module Skiplist
( packageName,
content,
attrPath,
checkResult,
python,
)
where
import Data.Foldable (find)
import qualified Data.Text as T
import OurPrelude
type Skiplist = [(Text -> Bool, Text)]
type TextSkiplister m =
(MonadError Text m) =>
Text ->
m ()
attrPath :: TextSkiplister m
attrPath :: Text -> m ()
attrPath = Skiplist -> TextSkiplister m
forall (m :: * -> *). Skiplist -> TextSkiplister m
skiplister Skiplist
attrPathList
packageName :: TextSkiplister m
packageName :: Text -> m ()
packageName Text
name =
if Text
name Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"elementary-xfce-icon-theme"
then () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
else Skiplist -> Text -> m ()
forall (m :: * -> *). Skiplist -> TextSkiplister m
skiplister Skiplist
nameList Text
name
content :: TextSkiplister m
content :: Text -> m ()
content = Skiplist -> TextSkiplister m
forall (m :: * -> *). Skiplist -> TextSkiplister m
skiplister Skiplist
contentList
checkResult :: TextSkiplister m
checkResult :: Text -> m ()
checkResult = Skiplist -> TextSkiplister m
forall (m :: * -> *). Skiplist -> TextSkiplister m
skiplister Skiplist
checkResultList
attrPathList :: Skiplist
attrPathList :: Skiplist
attrPathList =
[ Text -> Text -> (Text -> Bool, Text)
prefix
Text
"lua"
Text
"Packages for lua are currently skipped. https://github.com/NixOS/nixpkgs/pull/37501#issuecomment-375169646",
Text -> Text -> (Text -> Bool, Text)
prefix Text
"lxqt" Text
"Packages for lxqt are currently skipped.",
Text -> Text -> (Text -> Bool, Text)
prefix
Text
"altcoins.bitcoin"
Text
"@roconnor asked for a skip on this until something can be done with GPG signatures https://github.com/NixOS/nixpkgs/commit/77f3ac7b7638b33ab198330eaabbd6e0a2e751a9",
Text -> Text -> (Text -> Bool, Text)
eq Text
"sqlite-interactive" Text
"it is an override",
Text -> Text -> (Text -> Bool, Text)
eq Text
"harfbuzzFull" Text
"it is an override",
Text -> Text -> (Text -> Bool, Text)
prefix
Text
"mate"
Text
"mate packages are upgraded in lockstep https://github.com/NixOS/nixpkgs/pull/50695#issuecomment-441338593",
Text -> Text -> (Text -> Bool, Text)
prefix
Text
"deepin"
Text
"deepin packages are upgraded in lockstep https://github.com/NixOS/nixpkgs/pull/52327#issuecomment-447684194",
Text -> Text -> (Text -> Bool, Text)
prefix
Text
"element-desktop"
Text
"@Ma27 asked to skip",
Text -> Text -> (Text -> Bool, Text)
prefix
Text
"element-web"
Text
"has to be updated along with element-desktop",
Text -> Text -> (Text -> Bool, Text)
prefix
Text
"keybinder"
Text
"it has weird tags. see nixpkgs-update#232"
]
nameList :: Skiplist
nameList :: Skiplist
nameList =
[ Text -> Text -> (Text -> Bool, Text)
prefix Text
"r-" Text
"we don't know how to find the attrpath for these",
Text -> Text -> (Text -> Bool, Text)
infixOf Text
"jquery" Text
"this isn't a real package",
Text -> Text -> (Text -> Bool, Text)
infixOf Text
"google-cloud-sdk" Text
"complicated package",
Text -> Text -> (Text -> Bool, Text)
infixOf Text
"github-release" Text
"complicated package",
Text -> Text -> (Text -> Bool, Text)
infixOf
Text
"libxc"
Text
"currently people don't want to update this https://github.com/NixOS/nixpkgs/pull/35821",
Text -> Text -> (Text -> Bool, Text)
infixOf Text
"perl" Text
"currently don't know how to update perl",
Text -> Text -> (Text -> Bool, Text)
infixOf Text
"cdrtools" Text
"We keep downgrading this by accident.",
Text -> Text -> (Text -> Bool, Text)
infixOf Text
"gst" Text
"gstreamer plugins are kept in lockstep.",
Text -> Text -> (Text -> Bool, Text)
infixOf Text
"electron" Text
"multi-platform srcs in file.",
Text -> Text -> (Text -> Bool, Text)
infixOf
Text
"linux-headers"
Text
"Not updated until many packages depend on it (part of stdenv).",
Text -> Text -> (Text -> Bool, Text)
infixOf Text
"xfce" Text
"@volth asked to not update xfce",
Text -> Text -> (Text -> Bool, Text)
infixOf Text
"cmake-cursesUI-qt4UI" Text
"Derivation file is complicated",
Text -> Text -> (Text -> Bool, Text)
infixOf Text
"iana-etc" Text
"@mic92 takes care of this package",
Text -> Text -> (Text -> Bool, Text)
infixOf
Text
"checkbashism"
Text
"needs to be fixed, see https://github.com/NixOS/nixpkgs/pull/39552",
Text -> Text -> (Text -> Bool, Text)
eq Text
"isl" Text
"multi-version long building package",
Text -> Text -> (Text -> Bool, Text)
infixOf Text
"qscintilla" Text
"https://github.com/ryantm/nixpkgs-update/issues/51",
Text -> Text -> (Text -> Bool, Text)
eq Text
"itstool" Text
"https://github.com/NixOS/nixpkgs/pull/41339",
Text -> Text -> (Text -> Bool, Text)
infixOf
Text
"virtualbox"
Text
"nixpkgs-update cannot handle updating the guest additions https://github.com/NixOS/nixpkgs/pull/42934",
Text -> Text -> (Text -> Bool, Text)
eq
Text
"avr-binutils"
Text
"https://github.com/NixOS/nixpkgs/pull/43787#issuecomment-408649537",
Text -> Text -> (Text -> Bool, Text)
eq
Text
"iasl"
Text
"two updates had to be reverted, https://github.com/NixOS/nixpkgs/pull/46272",
Text -> Text -> (Text -> Bool, Text)
eq
Text
"meson"
Text
"https://github.com/NixOS/nixpkgs/pull/47024#issuecomment-423300633",
Text -> Text -> (Text -> Bool, Text)
eq
Text
"burp"
Text
"skipped until better versioning schema https://github.com/NixOS/nixpkgs/pull/46298#issuecomment-419536301",
Text -> Text -> (Text -> Bool, Text)
eq Text
"chromedriver" Text
"complicated package",
Text -> Text -> (Text -> Bool, Text)
eq
Text
"gitlab-shell"
Text
"@globin asked to skip in https://github.com/NixOS/nixpkgs/pull/52294#issuecomment-447653417",
Text -> Text -> (Text -> Bool, Text)
eq
Text
"gitlab-workhorse"
Text
"@globin asked to skip in https://github.com/NixOS/nixpkgs/pull/52286#issuecomment-447653409",
Text -> Text -> (Text -> Bool, Text)
eq Text
"reposurgeon" Text
"takes way too long to build",
Text -> Text -> (Text -> Bool, Text)
eq Text
"kodelife" Text
"multiple system hashes need to be updated at once",
Text -> Text -> (Text -> Bool, Text)
eq Text
"openbazaar" Text
"multiple system hashes need to be updated at once",
Text -> Text -> (Text -> Bool, Text)
eq Text
"eaglemode" Text
"build hangs or takes way too long",
Text -> Text -> (Text -> Bool, Text)
eq Text
"autoconf" Text
"@prusnak asked to skip",
Text -> Text -> (Text -> Bool, Text)
eq Text
"abseil-cpp" Text
"@andersk asked to skip"
]
contentList :: Skiplist
contentList :: Skiplist
contentList =
[ Text -> Text -> (Text -> Bool, Text)
infixOf Text
"nixpkgs-update: no auto update" Text
"Derivation file opts-out of auto-updates",
Text -> Text -> (Text -> Bool, Text)
infixOf Text
"DO NOT EDIT" Text
"Derivation file says not to edit it",
Text -> Text -> (Text -> Bool, Text)
infixOf Text
"Do not edit!" Text
"Derivation file says not to edit it",
Text -> Text -> (Text -> Bool, Text)
infixOf Text
"buildRustCrate" Text
"Derivation contains buildRustCrate",
Text -> Text -> (Text -> Bool, Text)
infixOf Text
"buildRubyGem" Text
"Derivation contains buildRubyGem",
Text -> Text -> (Text -> Bool, Text)
infixOf Text
"bundlerEnv" Text
"Derivation contains bundlerEnv",
Text -> Text -> (Text -> Bool, Text)
infixOf Text
"buildPerlPackage" Text
"Derivation contains buildPerlPackage",
Text -> Text -> (Text -> Bool, Text)
infixOf Text
"goDeps" Text
"Derivation contains goDeps attribute",
Text -> Text -> (Text -> Bool, Text)
infixOf Text
"https://downloads.haskell.org/ghc/" Text
"GHC packages are versioned per file",
Text -> Text -> (Text -> Bool, Text)
infixOf Text
"pantheon" Text
"Do not update Pantheon during a release cycle"
]
checkResultList :: Skiplist
checkResultList :: Skiplist
checkResultList =
[ Text -> Text -> (Text -> Bool, Text)
infixOf
Text
"busybox"
Text
"- busybox result is not automatically checked, because some binaries kill the shell",
Text -> Text -> (Text -> Bool, Text)
infixOf
Text
"fcitx"
Text
"- fcitx result is not automatically checked, because some binaries gets stuck in daemons",
Text -> Text -> (Text -> Bool, Text)
infixOf
Text
"x2goclient"
Text
"- x2goclient result is not automatically checked, because some binaries don't timeout properly",
Text -> Text -> (Text -> Bool, Text)
infixOf
Text
"kicad"
Text
"- kicad result is not automatically checked, because some binaries don't timeout properly",
Text -> Text -> (Text -> Bool, Text)
infixOf
Text
"gjs"
Text
"- gjs result is not automatically checked, because some tests take a long time to run",
Text -> Text -> (Text -> Bool, Text)
infixOf
Text
"casperjs"
Text
"- casperjs result is not automatically checked, because some tests take a long time to run"
]
skiplister :: Skiplist -> TextSkiplister m
skiplister :: Skiplist -> TextSkiplister m
skiplister Skiplist
skiplist Text
input = Maybe Text -> (Text -> m Any) -> m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ Maybe Text
result Text -> m Any
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError
where
result :: Maybe Text
result = (Text -> Bool, Text) -> Text
forall a b. (a, b) -> b
snd ((Text -> Bool, Text) -> Text)
-> Maybe (Text -> Bool, Text) -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((Text -> Bool, Text) -> Bool)
-> Skiplist -> Maybe (Text -> Bool, Text)
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (\(Text -> Bool
isSkiplisted, Text
_) -> Text -> Bool
isSkiplisted Text
input) Skiplist
skiplist
prefix :: Text -> Text -> (Text -> Bool, Text)
prefix :: Text -> Text -> (Text -> Bool, Text)
prefix Text
part Text
reason = ((Text
part Text -> Text -> Bool
`T.isPrefixOf`), Text
reason)
infixOf :: Text -> Text -> (Text -> Bool, Text)
infixOf :: Text -> Text -> (Text -> Bool, Text)
infixOf Text
part Text
reason = ((Text
part Text -> Text -> Bool
`T.isInfixOf`), Text
reason)
eq :: Text -> Text -> (Text -> Bool, Text)
eq :: Text -> Text -> (Text -> Bool, Text)
eq Text
part Text
reason = ((Text
part Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==), Text
reason)
python :: Monad m => Int -> Text -> ExceptT Text m ()
python :: Int -> Text -> ExceptT Text m ()
python Int
numPackageRebuilds Text
derivationContents =
Text -> Bool -> ExceptT Text m ()
forall (m :: * -> *) e. Monad m => e -> Bool -> ExceptT e m ()
tryAssert
( Text
"Python package with too many package rebuilds "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (String -> Text
T.pack (String -> Text) -> (Int -> String) -> Int -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
forall a. Show a => a -> String
show) Int
numPackageRebuilds
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" > "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Show a => a -> Text
tshow Int
maxPackageRebuild
)
(Bool -> Bool
not Bool
isPython Bool -> Bool -> Bool
|| Int
numPackageRebuilds Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
maxPackageRebuild)
where
isPython :: Bool
isPython = Text
"buildPythonPackage" Text -> Text -> Bool
`T.isInfixOf` Text
derivationContents
maxPackageRebuild :: Int
maxPackageRebuild = Int
25