treewide: light relude linting (#906)

* treewide: light relude linting

Provided `relude's` `.hlint.yaml` locally.

To my taste most of the suggestions are specific to `relude` and can be
considered harmful for future portability.

Only the `(fmap . fmap) == <<$>>` & `*.singleton == one`, I'd considered
somewhat reasonable to maybe thinnk about adopting.

The flip of the arguments in `whenJust` and so on - surprised me.

These here are what indeed is light and helps to clean-up a bit and in future
text data types & list migrations.

Most of the `relude` HLint rules I saw, I want to remove from the checks. So decisively not going to implement them
in CI.

* default.nix: upd default to GHC8104
This commit is contained in:
Anton Latukha 2021-03-26 21:10:41 +02:00 committed by GitHub
parent 1f59a229ad
commit 58cd8fa112
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
11 changed files with 75 additions and 73 deletions

View File

@ -102,7 +102,7 @@ jobs:
signingKey: '${{ secrets.CACHIX_SIGNING_KEY }}'
- name: "Determined Nix-build"
env:
compiler: "ghc8103"
compiler: "ghc8104"
buildFromSdist: "true"
buildStrictly: "true"
linkWithGold: "true"

View File

@ -1,7 +1,7 @@
{
# For current default and explicitly supported GHCs https://search.nixos.org/packages?query=ghc&from=0&size=500&channel=unstable, Nixpkgs implicitly supports older minor versions also, until the configuration departs from compatibility with them.
# Compiler in a form ghc8101 <- GHC 8.10.1, just remove spaces and dots
compiler ? "ghc8103"
compiler ? "ghc8104"
# Deafult.nix is a unit package abstraciton that allows to abstract over packages even in monorepos:
# Example: pass --arg cabalName --arg packageRoot "./subprojectDir", or map default.nix over a list of tiples for subprojects.

View File

@ -26,8 +26,6 @@ import Nix.Scope
import Nix.Utils
import Nix.Value.Monad ( demand )
import qualified Data.List as List
import qualified Data.Maybe as Maybe
import qualified Data.HashMap.Lazy
import Data.Char ( isSpace )
import Data.List ( dropWhileEnd )
@ -116,7 +114,7 @@ main' iniVal =
optMatcher command options arguments
x -> cmd $ String.unwords x
)
(String.words . toString <$> Text.lines f)
(String.words . toString <$> lines f)
handleMissing e
| Error.isDoesNotExistError e = pure ""
@ -133,7 +131,7 @@ main' iniVal =
-> m ()
optMatcher s [] _ = liftIO $ putStrLn $ "No such command :" <> s
optMatcher s ((x, m) : xs) args
| s `List.isPrefixOf` x = m args
| s `isPrefixOf` x = m args
| otherwise = optMatcher s xs args
@ -170,7 +168,7 @@ initState mIni = do
IState
Nothing
(Data.HashMap.Lazy.fromList $
("builtins", builtins) : fmap ("input",) (Maybe.maybeToList mIni)
("builtins", builtins) : fmap ("input",) (maybeToList mIni)
)
defReplConfig
{ cfgStrict = strict opts
@ -272,7 +270,7 @@ printValue :: (MonadNix e t f m, MonadIO m)
-> Repl e t f m ()
printValue val = do
cfg <- replCfg <$> get
lift $ lift $ do
lift $ lift $
if
| cfgStrict cfg -> liftIO . print . prettyNValue =<< normalForm val
| cfgValues cfg -> liftIO . print . prettyNValueProv =<< removeEffects val
@ -376,7 +374,7 @@ completeFunc reversedPrev word
$ fmap helpOptionName (helpOptions :: HelpOptions e t f m)
-- Files
| any (`List.isPrefixOf` word) [ "/", "./", "../", "~/" ] =
| any (`isPrefixOf` word) [ "/", "./", "../", "~/" ] =
listFiles word
-- Attributes of sets in REPL context
@ -406,7 +404,7 @@ completeFunc reversedPrev word
<> (toString <$> shortBuiltins)
where
listCompletion = fmap simpleCompletion . filter (word `List.isPrefixOf`)
listCompletion = fmap simpleCompletion . filter (word `isPrefixOf`)
notFinished x = x { isFinished = False }

View File

@ -2,6 +2,6 @@ attrs@{...}:
let defaultAttrs = {
# Defaults are put in this form deliberately. Details: #748
withHoogle = true;
compiler = "ghc8101";
compiler = "ghc8104";
};
in (import ./. (defaultAttrs // attrs)).env

View File

@ -11,13 +11,14 @@ module Nix.Effects.Basic where
import Prelude hiding ( traceM
, head
)
import Relude.Unsafe ( head )
import Nix.Utils
import Control.Monad ( foldM )
import qualified Data.HashMap.Lazy as M
import Data.List hiding ( elem )
import Data.List.Split
import Data.List.Split ( splitOn )
import qualified Data.Text as Text
import Data.Text.Prettyprint.Doc
import Data.Text.Prettyprint.Doc ( fillSep )
import System.FilePath
import Nix.Convert
import Nix.Effects
import Nix.Exec ( MonadNix
@ -32,7 +33,6 @@ import Nix.Scope
import Nix.String
import Nix.Value
import Nix.Value.Monad
import System.FilePath
#ifdef MIN_VERSION_ghc_datasize
#if MIN_VERSION_ghc_datasize(0,2,0)

View File

@ -10,9 +10,6 @@
module Nix.Effects.Derivation ( defaultDerivationStrict ) where
import Prelude hiding ( elem
, readFile
)
import Nix.Utils
import Data.Char ( isAscii
, isAlphaNum
@ -20,12 +17,10 @@ import Data.Char ( isAscii
import qualified Data.HashMap.Lazy as M
import qualified Data.HashMap.Strict as MS
import qualified Data.HashSet as S
-- Please, move to NonEmpty
import Data.List
import Data.Foldable ( foldl )
import qualified Data.Map.Strict as Map
import qualified Data.Set as Set
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import Nix.Atoms
import Nix.Convert
@ -47,6 +42,7 @@ import qualified System.Nix.StorePath as Store
import Text.Megaparsec
import Text.Megaparsec.Char
import Prelude hiding (readFile)
data Derivation = Derivation
@ -72,7 +68,7 @@ makeStorePathName name = case Store.makeStorePathName name of
Right spname -> pure spname
parsePath :: (Framed e m) => Text -> m Store.StorePath
parsePath p = case Store.parsePath "/nix/store" (Text.encodeUtf8 p) of
parsePath p = case Store.parsePath "/nix/store" (encodeUtf8 p) of
Left err -> throwError $ ErrorCall $ "Cannot parse store path " <> show p <> ":\n" <> show err
Right path -> pure path
@ -86,29 +82,45 @@ writeDerivation drv@Derivation{inputs, name} = do
-- | Traverse the graph of inputDrvs to replace fixed output derivations with their fixed output hash.
-- this avoids propagating changes to their .drv when the output hash stays the same.
hashDerivationModulo :: (MonadNix e t f m, MonadState (b, MS.HashMap Text Text) m) => Derivation -> m (Store.Digest 'Store.SHA256)
hashDerivationModulo (Derivation {
mFixed = Just (Store.SomeDigest (digest :: Store.Digest hashType)),
outputs,
hashMode
}) = case Map.toList outputs of
[("out", path)] -> pure $ Store.hash @'Store.SHA256 $ Text.encodeUtf8
$ "fixed:out"
<> (if hashMode == Recursive then ":r" else "")
<> ":" <> (Store.algoName @hashType)
<> ":" <> Store.encodeInBase Store.Base16 digest
<> ":" <> path
outputsList -> throwError $ ErrorCall $ "This is weird. A fixed output drv should only have one output named 'out'. Got " <> show outputsList
hashDerivationModulo drv@Derivation{inputs = (inputSrcs, inputDrvs)} = do
cache <- gets snd
inputsModulo <- Map.fromList <$> forM (Map.toList inputDrvs) (\(path, outs) ->
case MS.lookup path cache of
Just hash -> pure (hash, outs)
Nothing -> do
drv' <- readDerivation $ toString path
hash <- Store.encodeInBase Store.Base16 <$> hashDerivationModulo drv'
pure (hash, outs)
)
pure $ Store.hash @'Store.SHA256 $ Text.encodeUtf8 $ unparseDrv (drv {inputs = (inputSrcs, inputsModulo)})
hashDerivationModulo
Derivation
{ mFixed = Just (Store.SomeDigest (digest :: Store.Digest hashType))
, outputs
, hashMode
} =
case Map.toList outputs of
[("out", path)] -> pure $
Store.hash @'Store.SHA256 $
encodeUtf8 $
"fixed:out"
<> (if hashMode == Recursive then ":r" else "")
<> ":" <> (Store.algoName @hashType)
<> ":" <> Store.encodeInBase Store.Base16 digest
<> ":" <> path
_outputsList -> throwError $ ErrorCall $ "This is weird. A fixed output drv should only have one output named 'out'. Got " <> show _outputsList
hashDerivationModulo
drv@Derivation
{ inputs = ( inputSrcs
, inputDrvs
)
} =
do
cache <- gets snd
inputsModulo <-
Map.fromList <$>
traverse
(\(path, outs) ->
maybe
(do
drv' <- readDerivation $ toString path
hash <- Store.encodeInBase Store.Base16 <$> hashDerivationModulo drv'
pure (hash, outs)
)
(\ hash -> pure (hash, outs))
(MS.lookup path cache)
)
(Map.toList inputDrvs)
pure $ Store.hash @'Store.SHA256 $ encodeUtf8 $ unparseDrv (drv {inputs = (inputSrcs, inputsModulo)})
unparseDrv :: Derivation -> Text
unparseDrv Derivation{..} = Text.append "Derive" $ parens
@ -150,7 +162,7 @@ unparseDrv Derivation{..} = Text.append "Derive" $ parens
readDerivation :: (Framed e m, MonadFile m) => FilePath -> m Derivation
readDerivation path = do
content <- Text.decodeUtf8 <$> readFile path
content <- decodeUtf8 <$> readFile path
either
(\ err -> throwError $ ErrorCall $ "Failed to parse " <> show path <> ":\n" <> show err)
pure
@ -259,11 +271,11 @@ defaultDerivationStrict = fromValue @(AttrSet (NValue t f m)) >=> \s -> do
where
pathToText = Text.decodeUtf8 . Store.storePathToRawFilePath
pathToText = decodeUtf8 . Store.storePathToRawFilePath
makeOutputPath o h n = do
name <- makeStorePathName (Store.unStorePathName n <> if o == "out" then "" else "-" <> o)
pure $ pathToText $ Store.makeStorePath "/nix/store" ("output:" <> Text.encodeUtf8 o) h name
pure $ pathToText $ Store.makeStorePath "/nix/store" ("output:" <> encodeUtf8 o) h name
toStorePaths ctx = foldl (flip addToInputs) (mempty, mempty) ctx
addToInputs (StringContext path kind) = case kind of

View File

@ -12,8 +12,8 @@
module Nix.Eval where
import Control.Monad
import Control.Monad.Fix
import Control.Monad ( foldM )
import Control.Monad.Fix ( MonadFix )
import Data.Semialign.Indexed ( ialignWith )
import Data.Fix ( Fix(Fix) )
import qualified Data.HashMap.Lazy as M

View File

@ -6,7 +6,6 @@ module Nix.Json where
import qualified Data.Aeson as A
import qualified Data.Aeson.Encoding as A
import qualified Data.HashMap.Lazy as HM
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL
import qualified Data.Vector as V
import Nix.Atoms
@ -22,7 +21,7 @@ nvalueToJSONNixString :: MonadNix e t f m => NValue t f m -> m NixString
nvalueToJSONNixString =
runWithStringContextT .
fmap
( TL.toStrict
( toStrict
. TL.decodeUtf8
. A.encodingToLazyByteString
. toEncodingSorted

View File

@ -67,7 +67,6 @@ import Data.Char ( isAlpha
import Data.Data ( Data(..) )
import Data.Fix ( Fix(..) )
import qualified Data.HashSet as HashSet
import qualified Data.List.NonEmpty as NE
import qualified Data.Map as Map
import Data.Text ( cons
, singleton
@ -386,7 +385,7 @@ argExpr =
-- there's a valid URI parse here.
onlyname =
msum
[ nixUri *> unexpected (Label ('v' NE.:| "alid uri"))
[ nixUri *> unexpected (Label ('v' :| "alid uri"))
, Param <$> identifier
]

View File

@ -13,14 +13,11 @@ module Nix.Render where
import Prelude hiding ( readFile )
#if !MIN_VERSION_base(4,13,0)
import Control.Monad.Fail ( MonadFail )
#endif
-- Please reduce Unsafe
import Relude.Unsafe ( read )
import qualified Data.ByteString as BS
import qualified Data.Set as Set
import Data.List ( maximum )
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import Nix.Utils.Fix1 ( Fix1T
, MonadFix1T )
import Nix.Expr.Types.Annotated
@ -29,8 +26,6 @@ import qualified System.Directory as S
import qualified System.Posix.Files as S
import Text.Megaparsec.Error
import Text.Megaparsec.Pos
-- Please reduce Unsafe
import Relude.Unsafe ( read )
class MonadFail m => MonadFile m where
readFile :: FilePath -> m ByteString
@ -91,13 +86,13 @@ renderLocation (SrcSpan (SourcePos file begLine begCol) (SourcePos file' endLine
if exist
then do
txt <- sourceContext file begLine begCol endLine endCol msg
pure
$ vsep
[ "In file "
<> errorContext file begLine begCol endLine endCol
<> ":"
, txt
]
pure $
vsep
[ "In file "
<> errorContext file begLine begCol endLine endCol
<> ":"
, txt
]
else pure msg
renderLocation (SrcSpan beg end) msg = fail $ "Don't know how to render range from " <> show beg <>" to " <> show end <>" for fail: " <> show msg
@ -115,8 +110,8 @@ sourceContext path (unPos -> begLine) (unPos -> _begCol) (unPos -> endLine) (unP
fmap pretty
. take (end' - beg')
. drop (pred beg')
. T.lines
. T.decodeUtf8
. lines
. decodeUtf8
<$> readFile path
let
nums = zipWith (curry (show . fst)) [beg' ..] ls

View File

@ -13,7 +13,6 @@ import Data.Algorithm.Diff
import Data.Algorithm.DiffOutput
import Data.Char
import Data.Fix
import qualified Data.List.NonEmpty as NE
import qualified Data.String as String
import Hedgehog
import qualified Hedgehog.Gen as Gen
@ -67,7 +66,7 @@ genString = Gen.choice
]
genAttrPath :: Gen (NAttrPath NExpr)
genAttrPath = (NE.:|) <$> genKeyName <*> Gen.list (Range.linear 0 4) genKeyName
genAttrPath = (:|) <$> genKeyName <*> Gen.list (Range.linear 0 4) genKeyName
genParams :: Gen (Params NExpr)
genParams = Gen.choice
@ -153,7 +152,7 @@ normalize = foldFix $ \case
r -> Fix r
where
normBinding (NamedVar path r pos) = NamedVar (NE.map normKey path) r pos
normBinding (NamedVar path r pos) = NamedVar (fmap normKey path) r pos
normBinding (Inherit mr names pos) = Inherit mr (fmap normKey names) pos
normKey (DynamicKey quoted) = DynamicKey (normAntiquotedString quoted)