Skip to content

Commit 2950fee

Browse files
committed
([] -> mempty)
There are some `(:|)` use. I looked carefully, but there still can be something, expecially in Repl or test parts of the code. The `mempty` of the left hand side should not be present. Also specially checked the shadowing case with: {-# OPTIONS_GHC -fno-warn-name-shadowing #-}, where were none.
1 parent a93bb66 commit 2950fee

27 files changed

+107
-107
lines changed

main/Repl.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -360,7 +360,7 @@ completeFunc reversedPrev word
360360
= do
361361
s <- get
362362
case Data.HashMap.Lazy.lookup var (replCtx s) of
363-
Nothing -> pure []
363+
Nothing -> pure mempty
364364
Just binding -> do
365365
candidates <- lift $ algebraicComplete subFields binding
366366
pure $ notFinished <$> listCompletion (Data.Text.unpack . (var <>) <$> candidates)
@@ -396,14 +396,14 @@ completeFunc reversedPrev word
396396
[_] -> pure $ keys m
397397
f:fs ->
398398
case Data.HashMap.Lazy.lookup f m of
399-
Nothing -> pure []
399+
Nothing -> pure mempty
400400
Just e ->
401401
demand e
402402
(\e' -> (fmap . fmap) (("." <> f) <>) $ algebraicComplete fs e')
403403

404404
in case val of
405405
NVSet xs _ -> withMap xs
406-
_ -> pure []
406+
_ -> pure mempty
407407

408408
-- HelpOption inspired by Dhall Repl
409409
-- with `Doc` instead of String for syntax and doc

src/Nix/Builtins.hs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -316,15 +316,15 @@ foldNixPath
316316
foldNixPath f z = do
317317
mres <- lookupVar "__includes"
318318
dirs <- case mres of
319-
Nothing -> pure []
319+
Nothing -> pure mempty
320320
Just v -> demand v $ fromValue . Deeper
321321
mPath <- getEnvVar "NIX_PATH"
322322
mDataDir <- getEnvVar "NIX_DATA_DIR"
323323
dataDir <- maybe getDataDir pure mDataDir
324324
foldrM go z
325325
$ fmap (fromInclude . stringIgnoreContext) dirs
326326
<> case mPath of
327-
Nothing -> []
327+
Nothing -> mempty
328328
Just str -> uriAwareSplit (Text.pack str)
329329
<> [ fromInclude $ Text.pack $ "nix=" <> dataDir <> "/nix/corepkgs" ]
330330
where
@@ -336,7 +336,7 @@ foldNixPath f z = do
336336
_ -> throwError $ ErrorCall $ "Unexpected entry in NIX_PATH: " <> show x
337337

338338
nixPath :: MonadNix e t f m => m (NValue t f m)
339-
nixPath = fmap nvList $ flip foldNixPath [] $ \p mn ty rest ->
339+
nixPath = fmap nvList $ flip foldNixPath mempty $ \p mn ty rest ->
340340
pure
341341
$ flip nvSet mempty ( M.fromList
342342
[ case ty of
@@ -512,7 +512,7 @@ versionComponentSeparators = ".-"
512512

513513
splitVersion :: Text -> [VersionComponent]
514514
splitVersion s = case Text.uncons s of
515-
Nothing -> []
515+
Nothing -> mempty
516516
Just (h, t)
517517
| h `elem` versionComponentSeparators
518518
-> splitVersion t
@@ -575,7 +575,7 @@ splitDrvName s =
575575
breakAfterFirstItem :: (a -> Bool) -> [a] -> ([a], [a])
576576
breakAfterFirstItem f = \case
577577
h : t -> let (a, b) = break f t in (h : a, b)
578-
[] -> ([], [])
578+
[] -> (mempty, mempty)
579579
(namePieces, versionPieces) =
580580
breakAfterFirstItem isFirstVersionPiece pieces
581581
in
@@ -910,7 +910,7 @@ genericClosure = fromValue @(AttrSet (NValue t f m)) >=> \s ->
910910
-> [NValue t f m]
911911
-> Set (WValue t f m)
912912
-> m (Set (WValue t f m), [NValue t f m])
913-
go _ [] ks = pure (ks, [])
913+
go _ [] ks = pure (ks, mempty)
914914
go op (t : ts) ks = demand t $ \v -> fromValue @(AttrSet (NValue t f m)) v >>= \s -> do
915915
k <- attrsetGet "key" s
916916
demand k $ \k' -> do
@@ -1480,7 +1480,7 @@ appendContext x y = demand x $ \x' -> demand y $ \y' -> case (x', y') of
14801480
allOutputs <- maybe (pure False) (demand ?? fromValue)
14811481
$ M.lookup "allOutputs" attrs
14821482
outputs <- case M.lookup "outputs" attrs of
1483-
Nothing -> pure []
1483+
Nothing -> pure mempty
14841484
Just os -> demand os $ \case
14851485
NVList vs ->
14861486
forM vs $ fmap stringIgnoreContext . fromValue

src/Nix/Cited.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -38,7 +38,7 @@ data NCited m v a = NCited
3838
deriving (Generic, Typeable, Functor, Foldable, Traversable, Show)
3939

4040
instance Applicative (NCited m v) where
41-
pure = NCited []
41+
pure = NCited mempty
4242
NCited xs f <*> NCited ys x = NCited (xs <> ys) (f x)
4343

4444
instance Comonad (NCited m v) where

src/Nix/Cited/Basic.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -66,11 +66,11 @@ instance ( Has e Options
6666
(Fix (Compose (Ann s e))))) =
6767
let e' = Compose (Ann s (Nothing <$ e))
6868
in [Provenance scope e']
69-
go _ = []
69+
go _ = mempty
7070
ps = concatMap (go . frame) frames
7171

7272
fmap (Cited . NCited ps) . thunk $ mv
73-
else fmap (Cited . NCited []) . thunk $ mv
73+
else fmap (Cited . NCited mempty) . thunk $ mv
7474

7575
thunkId (Cited (NCited _ t)) = thunkId @_ @m t
7676

src/Nix/Context.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -32,4 +32,4 @@ instance Has (Context m t) Options where
3232
hasLens f a = (\x -> a { options = x }) <$> f (options a)
3333

3434
newContext :: Options -> Context m t
35-
newContext = Context emptyScopes nullSpan []
35+
newContext = Context emptyScopes nullSpan mempty

src/Nix/Effects/Basic.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -73,7 +73,7 @@ expandHomePath p = pure p
7373
-- parent may be a different directory from @a@. See the discussion at
7474
-- https://hackage.haskell.org/package/directory-1.3.1.5/docs/System-Directory.html#v:canonicalizePath
7575
removeDotDotIndirections :: FilePath -> FilePath
76-
removeDotDotIndirections = intercalate "/" . go [] . splitOn "/"
76+
removeDotDotIndirections = intercalate "/" . go mempty . splitOn "/"
7777
where
7878
go s [] = reverse s
7979
go (_ : s) (".." : rest) = go s rest

src/Nix/Effects/Derivation.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -73,7 +73,7 @@ defaultDerivation = Derivation
7373
, inputs = (Set.empty, Map.empty)
7474
, platform = undefined
7575
, builder = undefined
76-
, args = []
76+
, args = mempty
7777
, env = Map.empty
7878
, mFixed = Nothing
7979
, hashMode = Flat
@@ -297,7 +297,7 @@ buildDerivationWithContext drvAttrs = do
297297
useJson <- getAttrOr "__structuredAttrs" False $ pure
298298
ignoreNulls <- getAttrOr "__ignoreNulls" False $ pure
299299

300-
args <- getAttrOr "args" [] $ mapM (fromValue' >=> extractNixString)
300+
args <- getAttrOr "args" mempty $ mapM (fromValue' >=> extractNixString)
301301
builder <- getAttr "builder" $ extractNixString
302302
platform <- getAttr "system" $ extractNoCtx >=> assertNonNull
303303
mHash <- getAttrOr "outputHash" Nothing $ extractNoCtx >=> (pure . pure)

src/Nix/Eval.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -267,7 +267,7 @@ evalBinds recursive binds = do
267267
h :| t -> evalSetterKeyName h >>= \case
268268
Nothing ->
269269
pure
270-
( []
270+
( mempty
271271
, nullPos
272272
, toValue @(AttrSet v, AttrSet SourcePos) (mempty, mempty)
273273
)
@@ -279,7 +279,7 @@ evalBinds recursive binds = do
279279
go pathExpr <&> \case
280280
-- When there are no path segments, e.g. `${null} = 5;`, we don't
281281
-- bind anything
282-
([], _, _) -> []
282+
([], _, _) -> mempty
283283
result -> [result]
284284

285285
go scope (Inherit ms names pos) =

src/Nix/Expr/Shorthands.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -32,13 +32,13 @@ mkFloatF = NConstant . NFloat
3232
-- | Make a regular (double-quoted) string.
3333
mkStr :: Text -> NExpr
3434
mkStr = Fix . NStr . DoubleQuoted . \case
35-
"" -> []
35+
"" -> mempty
3636
x -> [Plain x]
3737

3838
-- | Make an indented string.
3939
mkIndentedStr :: Int -> Text -> NExpr
4040
mkIndentedStr w = Fix . NStr . Indented w . \case
41-
"" -> []
41+
"" -> mempty
4242
x -> [Plain x]
4343

4444
-- | Make a path. Use 'True' if the path should be read from the
@@ -78,7 +78,7 @@ mkSynHoleF :: Text -> NExprF a
7878
mkSynHoleF = NSynHole
7979

8080
mkSelector :: Text -> NAttrPath NExpr
81-
mkSelector = (:| []) . StaticKey
81+
mkSelector = (:| mempty) . StaticKey
8282

8383
mkBool :: Bool -> NExpr
8484
mkBool = Fix . mkBoolF
@@ -231,5 +231,5 @@ infixl 1 @@
231231
infixr 1 ==>
232232

233233
(@.) :: NExpr -> Text -> NExpr
234-
obj @. name = Fix (NSelect obj (StaticKey name :| []) Nothing)
234+
obj @. name = Fix (NSelect obj (StaticKey name :| mempty) Nothing)
235235
infixl 2 @.

src/Nix/Expr/Strings.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,7 @@ import Nix.Expr
1515

1616
-- | Merge adjacent 'Plain' values with 'mappend'.
1717
mergePlain :: [Antiquoted Text r] -> [Antiquoted Text r]
18-
mergePlain [] = []
18+
mergePlain [] = mempty
1919
mergePlain (Plain a : EscapedNewline : Plain b : xs) =
2020
mergePlain (Plain (a <> "\n" <> b) : xs)
2121
mergePlain (Plain a : Plain b : xs) = mergePlain (Plain (a <> b) : xs)
@@ -45,10 +45,10 @@ splitLines :: [Antiquoted Text r] -> [[Antiquoted Text r]]
4545
splitLines = uncurry (flip (:)) . go where
4646
go (Plain t : xs) = (Plain l :) <$> foldr f (go xs) ls where
4747
(l : ls) = T.split (== '\n') t
48-
f prefix (finished, current) = ((Plain prefix : current) : finished, [])
48+
f prefix (finished, current) = ((Plain prefix : current) : finished, mempty)
4949
go (Antiquoted a : xs) = (Antiquoted a :) <$> go xs
5050
go (EscapedNewline : xs) = (EscapedNewline :) <$> go xs
51-
go [] = ([], [])
51+
go [] = (mempty, mempty)
5252

5353
-- | Join a stream of strings containing antiquotes again. This is the inverse
5454
-- of 'splitLines'.
@@ -57,7 +57,7 @@ unsplitLines = intercalate [Plain "\n"]
5757

5858
-- | Form an indented string by stripping spaces equal to the minimal indent.
5959
stripIndent :: [Antiquoted Text r] -> NString r
60-
stripIndent [] = Indented 0 []
60+
stripIndent [] = Indented 0 mempty
6161
stripIndent xs =
6262
Indented minIndent
6363
. removePlainEmpty

0 commit comments

Comments
 (0)