Skip to content

Commit 8152874

Browse files
committed
(Nothing -> mempty)
Replaced only where the `(Semigroup a => Maybe a)` is already present, so does not change the signatures.
1 parent 768a14b commit 8152874

File tree

22 files changed

+55
-53
lines changed

22 files changed

+55
-53
lines changed

main/Main.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -53,15 +53,15 @@ main = do
5353
let file = addExtension (dropExtension path) "nixc"
5454
process opts (pure file) =<< liftIO (readCache path)
5555
Nothing -> case expression opts of
56-
Just s -> handleResult opts Nothing (parseNixTextLoc s)
56+
Just s -> handleResult opts mempty (parseNixTextLoc s)
5757
Nothing -> case fromFile opts of
5858
Just "-" -> mapM_ (processFile opts) . lines =<< liftIO getContents
5959
Just path ->
6060
mapM_ (processFile opts) . lines =<< liftIO (readFile path)
6161
Nothing -> case filePaths opts of
62-
[] -> withNixContext Nothing Repl.main
62+
[] -> withNixContext mempty Repl.main
6363
["-"] ->
64-
handleResult opts Nothing
64+
handleResult opts mempty
6565
. parseNixTextLoc
6666
=<< liftIO Text.getContents
6767
paths -> mapM_ (processFile opts) paths
@@ -102,8 +102,8 @@ main = do
102102
if evaluate opts
103103
then do
104104
val <- Nix.nixEvalExprLoc mpath expr
105-
withNixContext Nothing (Repl.main' $ pure val)
106-
else withNixContext Nothing Repl.main
105+
withNixContext mempty (Repl.main' $ pure val)
106+
else withNixContext mempty Repl.main
107107

108108
process opts mpath expr
109109
| evaluate opts

src/Nix/Builtins.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -331,7 +331,7 @@ foldNixPath f z = do
331331
fromInclude x | "://" `Text.isInfixOf` x = (x, PathEntryURI)
332332
| otherwise = (x, PathEntryPath)
333333
go (x, ty) rest = case Text.splitOn "=" x of
334-
[p] -> f (Text.unpack p) Nothing ty rest
334+
[p] -> f (Text.unpack p) mempty ty rest
335335
[n, p] -> f (Text.unpack p) (pure (Text.unpack n)) ty rest
336336
_ -> throwError $ ErrorCall $ "Unexpected entry in NIX_PATH: " <> show x
337337

src/Nix/Convert.hs

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -99,7 +99,7 @@ instance Convertible e t f m
9999
=> FromValue () m (NValue' t f m (NValue t f m)) where
100100
fromValueMay = \case
101101
NVConstant' NNull -> pure $ pure ()
102-
_ -> pure Nothing
102+
_ -> pure mempty
103103
fromValue v = fromValueMay v >>= \case
104104
Just b -> pure b
105105
_ -> throwError $ Expectation @t @f @m TNull (Free v)
@@ -155,9 +155,9 @@ instance ( Convertible e t f m
155155
. unStorePath
156156
<$> addPath p
157157
NVSet' s _ -> case M.lookup "outPath" s of
158-
Nothing -> pure Nothing
158+
Nothing -> pure mempty
159159
Just p -> fromValueMay p
160-
_ -> pure Nothing
160+
_ -> pure mempty
161161
fromValue v = fromValueMay v >>= \case
162162
Just b -> pure b
163163
_ -> throwError $ Expectation @t @f @m (TString NoContext) (Free v)
@@ -166,7 +166,7 @@ instance Convertible e t f m
166166
=> FromValue ByteString m (NValue' t f m (NValue t f m)) where
167167
fromValueMay = \case
168168
NVStr' ns -> pure $ encodeUtf8 <$> getStringNoContext ns
169-
_ -> pure Nothing
169+
_ -> pure mempty
170170
fromValue v = fromValueMay v >>= \case
171171
Just b -> pure b
172172
_ -> throwError $ Expectation @t @f @m (TString NoContext) (Free v)
@@ -193,7 +193,7 @@ instance Convertible e t f m
193193
=> FromValue [NValue t f m] m (NValue' t f m (NValue t f m)) where
194194
fromValueMay = \case
195195
NVList' l -> pure $ pure l
196-
_ -> pure Nothing
196+
_ -> pure mempty
197197
fromValue v = fromValueMay v >>= \case
198198
Just b -> pure b
199199
_ -> throwError $ Expectation @t @f @m TList (Free v)
@@ -204,7 +204,7 @@ instance ( Convertible e t f m
204204
=> FromValue [a] m (Deeper (NValue' t f m (NValue t f m))) where
205205
fromValueMay = \case
206206
Deeper (NVList' l) -> sequence <$> traverse fromValueMay l
207-
_ -> pure Nothing
207+
_ -> pure mempty
208208
fromValue v = fromValueMay v >>= \case
209209
Just b -> pure b
210210
_ -> throwError $ Expectation @t @f @m TList (Free (getDeeper v))
@@ -213,7 +213,7 @@ instance Convertible e t f m
213213
=> FromValue (AttrSet (NValue t f m)) m (NValue' t f m (NValue t f m)) where
214214
fromValueMay = \case
215215
NVSet' s _ -> pure $ pure s
216-
_ -> pure Nothing
216+
_ -> pure mempty
217217
fromValue v = fromValueMay v >>= \case
218218
Just b -> pure b
219219
_ -> throwError $ Expectation @t @f @m TSet (Free v)
@@ -224,7 +224,7 @@ instance ( Convertible e t f m
224224
=> FromValue (AttrSet a) m (Deeper (NValue' t f m (NValue t f m))) where
225225
fromValueMay = \case
226226
Deeper (NVSet' s _) -> sequence <$> traverse fromValueMay s
227-
_ -> pure Nothing
227+
_ -> pure mempty
228228
fromValue v = fromValueMay v >>= \case
229229
Just b -> pure b
230230
_ -> throwError $ Expectation @t @f @m TSet (Free (getDeeper v))
@@ -234,7 +234,7 @@ instance Convertible e t f m
234234
(NValue' t f m (NValue t f m)) where
235235
fromValueMay = \case
236236
NVSet' s p -> pure $ pure (s, p)
237-
_ -> pure Nothing
237+
_ -> pure mempty
238238
fromValue v = fromValueMay v >>= \case
239239
Just b -> pure b
240240
_ -> throwError $ Expectation @t @f @m TSet (Free v)
@@ -246,7 +246,7 @@ instance ( Convertible e t f m
246246
(Deeper (NValue' t f m (NValue t f m))) where
247247
fromValueMay = \case
248248
Deeper (NVSet' s p) -> fmap (, p) . sequence <$> traverse fromValueMay s
249-
_ -> pure Nothing
249+
_ -> pure mempty
250250
fromValue v = fromValueMay v >>= \case
251251
Just b -> pure b
252252
_ -> throwError $ Expectation @t @f @m TSet (Free (getDeeper v))

src/Nix/Effects/Basic.hs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -107,7 +107,7 @@ findEnvPathM name = do
107107
then makeAbsolutePath @t @f $ absPath </> "default.nix"
108108
else pure absPath
109109
exists <- doesFileExist absFile
110-
pure $ if exists then pure absFile else Nothing
110+
pure $ if exists then pure absFile else mempty
111111

112112
findPathBy
113113
:: forall e t f m
@@ -117,7 +117,7 @@ findPathBy
117117
-> FilePath
118118
-> m FilePath
119119
findPathBy finder ls name = do
120-
mpath <- foldM go Nothing ls
120+
mpath <- foldM go mempty ls
121121
case mpath of
122122
Nothing ->
123123
throwError
@@ -134,14 +134,14 @@ findPathBy finder ls name = do
134134
demand l $ fromValue >=> \(s :: HashMap Text (NValue t f m)) -> do
135135
p <- resolvePath s
136136
demand p $ fromValue >=> \(Path path) -> case M.lookup "prefix" s of
137-
Nothing -> tryPath path Nothing
137+
Nothing -> tryPath path mempty
138138
Just pf -> demand pf $ fromValueMay >=> \case
139139
Just (nsPfx :: NixString) ->
140140
let pfx = stringIgnoreContext nsPfx
141141
in if not (Text.null pfx)
142142
then tryPath path (pure (Text.unpack pfx))
143-
else tryPath path Nothing
144-
_ -> tryPath path Nothing
143+
else tryPath path mempty
144+
_ -> tryPath path mempty
145145

146146
tryPath p (Just n) | n' : ns <- splitDirectories name, n == n' =
147147
finder $ p <///> joinPath ns
@@ -222,7 +222,7 @@ findPathM = findPathBy existingPath
222222
existingPath path = do
223223
apath <- makeAbsolutePath @t @f path
224224
exists <- doesPathExist apath
225-
pure $ if exists then pure apath else Nothing
225+
pure $ if exists then pure apath else mempty
226226

227227
defaultImportPath
228228
:: (MonadNix e t f m, MonadState (HashMap FilePath NExprLoc, b) m)

src/Nix/Effects/Derivation.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -300,7 +300,7 @@ buildDerivationWithContext drvAttrs = do
300300
args <- getAttrOr "args" mempty $ mapM (fromValue' >=> extractNixString)
301301
builder <- getAttr "builder" $ extractNixString
302302
platform <- getAttr "system" $ extractNoCtx >=> assertNonNull
303-
mHash <- getAttrOr "outputHash" Nothing $ extractNoCtx >=> (pure . pure)
303+
mHash <- getAttrOr "outputHash" mempty $ extractNoCtx >=> (pure . pure)
304304
hashMode <- getAttrOr "outputHashMode" Flat $ extractNoCtx >=> parseHashMode
305305
outputs <- getAttrOr "outputs" ["out"] $ mapM (fromValue' >=> extractNoCtx)
306306

src/Nix/Eval.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -358,7 +358,7 @@ evalSetterKeyName = \case
358358
DynamicKey k ->
359359
runAntiquoted "\n" assembleString (>>= fromValueMay) k <&> \case
360360
Just ns -> Just (stringIgnoreContext ns)
361-
_ -> Nothing
361+
_ -> mempty
362362

363363
assembleString
364364
:: forall v m

src/Nix/Expr/Shorthands.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -99,7 +99,7 @@ mkOper2 :: NBinaryOp -> NExpr -> NExpr -> NExpr
9999
mkOper2 op a = Fix . NBinary op a
100100

101101
mkParamset :: [(Text, Maybe NExpr)] -> Bool -> Params NExpr
102-
mkParamset params variadic = ParamSet params variadic Nothing
102+
mkParamset params variadic = ParamSet params variadic mempty
103103

104104
mkRecSet :: [Binding NExpr] -> NExpr
105105
mkRecSet = Fix . NSet NRecursive

src/Nix/Lint.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -372,7 +372,7 @@ lintBinaryOp op lsym rarg = do
372372
NMult -> check lsym rsym [TConstant [TInt]]
373373
NDiv -> check lsym rsym [TConstant [TInt]]
374374

375-
NUpdate -> check lsym rsym [TSet Nothing]
375+
NUpdate -> check lsym rsym [TSet mempty]
376376

377377
NConcat -> check lsym rsym [TList y]
378378
where

src/Nix/Options.hs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -43,28 +43,28 @@ defaultOptions current = Options { verbose = ErrorsOnly
4343
, thunks = False
4444
, values = False
4545
, showScopes = False
46-
, reduce = Nothing
46+
, reduce = mempty
4747
, reduceSets = False
4848
, reduceLists = False
4949
, parse = False
5050
, parseOnly = False
5151
, finder = False
52-
, findFile = Nothing
52+
, findFile = mempty
5353
, strict = False
5454
, evaluate = False
5555
, json = False
5656
, xml = False
57-
, attr = Nothing
57+
, attr = mempty
5858
, include = mempty
5959
, check = False
60-
, readFrom = Nothing
60+
, readFrom = mempty
6161
, cache = False
6262
, repl = False
6363
, ignoreErrors = False
64-
, expression = Nothing
64+
, expression = mempty
6565
, arg = mempty
6666
, argstr = mempty
67-
, fromFile = Nothing
67+
, fromFile = mempty
6868
, currentTime = current
6969
, filePaths = mempty
7070
}

src/Nix/Parser.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -492,7 +492,7 @@ identifier = lexeme $ try $ do
492492
ident <-
493493
cons
494494
<$> satisfy (\x -> isAlpha x || x == '_')
495-
<*> takeWhileP Nothing identLetter
495+
<*> takeWhileP mempty identLetter
496496
guard (not (ident `HashSet.member` reservedNames))
497497
pure ident
498498
where

0 commit comments

Comments
 (0)