Skip to content

Commit 1cb1b40

Browse files
committed
(return -> pure)
1 parent 729b5cb commit 1cb1b40

File tree

11 files changed

+91
-91
lines changed

11 files changed

+91
-91
lines changed

src/Nix/Cache.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -24,13 +24,13 @@ readCache path = do
2424
eres <- C.unsafeReadCompact path
2525
case eres of
2626
Left err -> error $ "Error reading cache file: " <> err
27-
Right expr -> return $ C.getCompact expr
27+
Right expr -> pure $ C.getCompact expr
2828
#else
2929
#ifdef MIN_VERSION_serialise
3030
eres <- S.deserialiseOrFail <$> BS.readFile path
3131
case eres of
3232
Left err -> error $ "Error reading cache file: " <> show err
33-
Right expr -> return expr
33+
Right expr -> pure expr
3434
#else
3535
error "readCache not implemented for this platform"
3636
#endif

src/Nix/Effects.hs

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -92,7 +92,7 @@ instance MonadIntrospect IO where
9292
#if MIN_VERSION_ghc_datasize(0,2,0)
9393
recursiveSize
9494
#else
95-
\_ -> return 0
95+
\_ -> pure 0
9696
#endif
9797
#else
9898
\_ -> pure 0
@@ -269,31 +269,31 @@ class Monad m => MonadStore m where
269269

270270
parseStoreResult :: Monad m => String -> (Either String a, [Store.Remote.Logger]) -> m (Either ErrorCall a)
271271
parseStoreResult name res = case res of
272-
(Left msg, logs) -> return $ Left $ ErrorCall $ "Failed to execute '" <> name <> "': " <> msg <> "\n" <> show logs
273-
(Right result, _) -> return $ Right result
272+
(Left msg, logs) -> pure $ Left $ ErrorCall $ "Failed to execute '" <> name <> "': " <> msg <> "\n" <> show logs
273+
(Right result, _) -> pure $ Right result
274274

275275
instance MonadStore IO where
276276

277277
addToStore name path recursive repair = case Store.makeStorePathName name of
278-
Left err -> return $ Left $ ErrorCall $ "String '" <> show name <> "' is not a valid path name: " <> err
278+
Left err -> pure $ Left $ ErrorCall $ "String '" <> show name <> "' is not a valid path name: " <> err
279279
Right pathName -> do
280280
-- TODO: redesign the filter parameter
281281
res <- Store.Remote.runStore $ Store.Remote.addToStore @'Store.SHA256 pathName path recursive (const False) repair
282282
parseStoreResult "addToStore" res >>= \case
283-
Left err -> return $ Left err
284-
Right storePath -> return $ Right $ StorePath $ T.unpack $ T.decodeUtf8 $ Store.storePathToRawFilePath storePath
283+
Left err -> pure $ Left err
284+
Right storePath -> pure $ Right $ StorePath $ T.unpack $ T.decodeUtf8 $ Store.storePathToRawFilePath storePath
285285

286286
addTextToStore' name text references repair = do
287287
res <- Store.Remote.runStore $ Store.Remote.addTextToStore name text references repair
288288
parseStoreResult "addTextToStore" res >>= \case
289-
Left err -> return $ Left err
290-
Right path -> return $ Right $ StorePath $ T.unpack $ T.decodeUtf8 $ Store.storePathToRawFilePath path
289+
Left err -> pure $ Left err
290+
Right path -> pure $ Right $ StorePath $ T.unpack $ T.decodeUtf8 $ Store.storePathToRawFilePath path
291291

292292
addTextToStore :: (Framed e m, MonadStore m) => StorePathName -> Text -> Store.StorePathSet -> RepairFlag -> m StorePath
293-
addTextToStore a b c d = either throwError return =<< addTextToStore' a b c d
293+
addTextToStore a b c d = either throwError pure =<< addTextToStore' a b c d
294294

295295
addPath :: (Framed e m, MonadStore m) => FilePath -> m StorePath
296-
addPath p = either throwError return =<< addToStore (T.pack $ takeFileName p) p True False
296+
addPath p = either throwError pure =<< addToStore (T.pack $ takeFileName p) p True False
297297

298298
toFile_ :: (Framed e m, MonadStore m) => FilePath -> String -> m StorePath
299299
toFile_ p contents = addTextToStore (T.pack p) (T.pack contents) HS.empty False

src/Nix/Effects/Basic.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -105,7 +105,7 @@ findEnvPathM name = do
105105
isDir <- doesDirectoryExist absPath
106106
absFile <- if isDir
107107
then makeAbsolutePath @t @f $ absPath </> "default.nix"
108-
else return absPath
108+
else pure absPath
109109
exists <- doesFileExist absFile
110110
pure $ if exists then pure absFile else Nothing
111111

src/Nix/Effects/Derivation.hs

Lines changed: 31 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -86,12 +86,12 @@ data HashMode = Flat | Recursive
8686
makeStorePathName :: (Framed e m) => Text -> m Store.StorePathName
8787
makeStorePathName name = case Store.makeStorePathName name of
8888
Left err -> throwError $ ErrorCall $ "Invalid name '" <> show name <> "' for use in a store path: " <> err
89-
Right spname -> return spname
89+
Right spname -> pure spname
9090

9191
parsePath :: (Framed e m) => Text -> m Store.StorePath
9292
parsePath p = case Store.parsePath "/nix/store" (Text.encodeUtf8 p) of
9393
Left err -> throwError $ ErrorCall $ "Cannot parse store path " <> show p <> ":\n" <> show err
94-
Right path -> return path
94+
Right path -> pure path
9595

9696
writeDerivation :: (Framed e m, MonadStore m) => Derivation -> m Store.StorePath
9797
writeDerivation drv@Derivation{inputs, name} = do
@@ -108,7 +108,7 @@ hashDerivationModulo (Derivation {
108108
outputs,
109109
hashMode
110110
}) = case Map.toList outputs of
111-
[("out", path)] -> return $ Store.hash @'Store.SHA256 $ Text.encodeUtf8
111+
[("out", path)] -> pure $ Store.hash @'Store.SHA256 $ Text.encodeUtf8
112112
$ "fixed:out"
113113
<> (if hashMode == Recursive then ":r" else "")
114114
<> ":" <> (Store.algoName @hashType)
@@ -119,13 +119,13 @@ hashDerivationModulo drv@Derivation{inputs = (inputSrcs, inputDrvs)} = do
119119
cache <- gets snd
120120
inputsModulo <- Map.fromList <$> forM (Map.toList inputDrvs) (\(path, outs) ->
121121
case MS.lookup path cache of
122-
Just hash -> return (hash, outs)
122+
Just hash -> pure (hash, outs)
123123
Nothing -> do
124124
drv' <- readDerivation $ Text.unpack path
125125
hash <- Store.encodeInBase Store.Base16 <$> hashDerivationModulo drv'
126-
return (hash, outs)
126+
pure (hash, outs)
127127
)
128-
return $ Store.hash @'Store.SHA256 $ Text.encodeUtf8 $ unparseDrv (drv {inputs = (inputSrcs, inputsModulo)})
128+
pure $ Store.hash @'Store.SHA256 $ Text.encodeUtf8 $ unparseDrv (drv {inputs = (inputSrcs, inputsModulo)})
129129

130130
unparseDrv :: Derivation -> Text
131131
unparseDrv Derivation{..} = Text.append "Derive" $ parens
@@ -169,7 +169,7 @@ readDerivation path = do
169169
content <- Text.decodeUtf8 <$> readFile path
170170
case parse derivationParser path content of
171171
Left err -> throwError $ ErrorCall $ "Failed to parse " <> show path <> ":\n" <> show err
172-
Right drv -> return drv
172+
Right drv -> pure drv
173173

174174
derivationParser :: Parsec () Text Derivation
175175
derivationParser = do
@@ -197,7 +197,7 @@ derivationParser = do
197197
let name = "" -- FIXME (extract from file path ?)
198198
let useJson = ["__json"] == Map.keys env
199199

200-
return $ Derivation {inputs = (inputSrcs, inputDrvs), ..}
200+
pure $ Derivation {inputs = (inputSrcs, inputDrvs), ..}
201201
where
202202
s :: Parsec () Text Text
203203
s = fmap Text.pack $ string "\"" *> manyTill (escaped <|> regular) (string "\"")
@@ -238,7 +238,7 @@ defaultDerivationStrict = fromValue @(AttrSet (NValue t f m)) >=> \s -> do
238238
Just (Store.SomeDigest digest) -> do
239239
let out = pathToText $ Store.makeFixedOutputPath "/nix/store" (hashMode drv == Recursive) digest drvName
240240
let env' = if useJson drv then env drv else Map.insert "out" out (env drv)
241-
return $ drv { inputs, env = env', outputs = Map.singleton "out" out }
241+
pure $ drv { inputs, env = env', outputs = Map.singleton "out" out }
242242

243243
Nothing -> do
244244
hash <- hashDerivationModulo $ drv
@@ -248,7 +248,7 @@ defaultDerivationStrict = fromValue @(AttrSet (NValue t f m)) >=> \s -> do
248248
else foldl' (\m k -> Map.insert k "" m) (env drv) (Map.keys $ outputs drv)
249249
}
250250
outputs' <- sequence $ Map.mapWithKey (\o _ -> makeOutputPath o hash drvName) (outputs drv)
251-
return $ drv
251+
pure $ drv
252252
{ inputs
253253
, outputs = outputs'
254254
, env = if useJson drv then env drv else Map.union outputs' (env drv)
@@ -265,15 +265,15 @@ defaultDerivationStrict = fromValue @(AttrSet (NValue t f m)) >=> \s -> do
265265
attrSet = M.map nvStr $ M.fromList $ ("drvPath", drvPathWithContext): Map.toList outputsWithContext
266266
-- TODO: Add location information for all the entries.
267267
-- here --v
268-
return $ nvSet attrSet M.empty
268+
pure $ nvSet attrSet M.empty
269269

270270
where
271271

272272
pathToText = Text.decodeUtf8 . Store.storePathToRawFilePath
273273

274274
makeOutputPath o h n = do
275275
name <- makeStorePathName (Store.unStorePathName n <> if o == "out" then "" else "-" <> o)
276-
return $ pathToText $ Store.makeStorePath "/nix/store" ("output:" <> Text.encodeUtf8 o) h name
276+
pure $ pathToText $ Store.makeStorePath "/nix/store" ("output:" <> Text.encodeUtf8 o) h name
277277

278278
toStorePaths ctx = foldl (flip addToInputs) (Set.empty, Map.empty) ctx
279279
addToInputs (StringContext path kind) = case kind of
@@ -294,43 +294,43 @@ buildDerivationWithContext drvAttrs = do
294294
drvName <- getAttr "name" $ extractNixString >=> assertDrvStoreName
295295
withFrame' Info (ErrorCall $ "While evaluating derivation " <> show drvName) $ do
296296

297-
useJson <- getAttrOr "__structuredAttrs" False $ return
298-
ignoreNulls <- getAttrOr "__ignoreNulls" False $ return
297+
useJson <- getAttrOr "__structuredAttrs" False $ pure
298+
ignoreNulls <- getAttrOr "__ignoreNulls" False $ pure
299299

300300
args <- getAttrOr "args" [] $ mapM (fromValue' >=> extractNixString)
301301
builder <- getAttr "builder" $ extractNixString
302302
platform <- getAttr "system" $ extractNoCtx >=> assertNonNull
303-
mHash <- getAttrOr "outputHash" Nothing $ extractNoCtx >=> (return . pure)
303+
mHash <- getAttrOr "outputHash" Nothing $ extractNoCtx >=> (pure . pure)
304304
hashMode <- getAttrOr "outputHashMode" Flat $ extractNoCtx >=> parseHashMode
305305
outputs <- getAttrOr "outputs" ["out"] $ mapM (fromValue' >=> extractNoCtx)
306306

307307
mFixedOutput <- case mHash of
308-
Nothing -> return Nothing
308+
Nothing -> pure Nothing
309309
Just hash -> do
310310
when (outputs /= ["out"]) $ lift $ throwError $ ErrorCall $ "Multiple outputs are not supported for fixed-output derivations"
311311
hashType <- getAttr "outputHashAlgo" $ extractNoCtx
312-
digest <- lift $ either (throwError . ErrorCall) return $ Store.mkNamedDigest hashType hash
313-
return $ pure digest
312+
digest <- lift $ either (throwError . ErrorCall) pure $ Store.mkNamedDigest hashType hash
313+
pure $ pure digest
314314

315315
-- filter out null values if needed.
316316
attrs <- if not ignoreNulls
317-
then return drvAttrs
317+
then pure drvAttrs
318318
else M.mapMaybe id <$> forM drvAttrs (demand' ?? (\case
319-
NVConstant NNull -> return Nothing
320-
value -> return $ pure value
319+
NVConstant NNull -> pure Nothing
320+
value -> pure $ pure value
321321
))
322322

323323
env <- if useJson
324324
then do
325325
jsonString :: NixString <- lift $ nvalueToJSONNixString $ flip nvSet M.empty $
326326
deleteKeys [ "args", "__ignoreNulls", "__structuredAttrs" ] attrs
327327
rawString :: Text <- extractNixString jsonString
328-
return $ Map.singleton "__json" rawString
328+
pure $ Map.singleton "__json" rawString
329329
else
330330
mapM (lift . coerceToString callFunc CopyToStore CoerceAny >=> extractNixString) $
331331
Map.fromList $ M.toList $ deleteKeys [ "args", "__ignoreNulls" ] attrs
332332

333-
return $ defaultDerivation { platform, builder, args, env, hashMode, useJson
333+
pure $ defaultDerivation { platform, builder, args, env, hashMode, useJson
334334
, name = drvName
335335
, outputs = Map.fromList $ fmap (\o -> (o, "")) outputs
336336
, mFixed = mFixedOutput
@@ -339,13 +339,13 @@ buildDerivationWithContext drvAttrs = do
339339
-- common functions, lifted to WithStringContextT
340340

341341
demand' :: NValue t f m -> (NValue t f m -> WithStringContextT m a) -> WithStringContextT m a
342-
demand' v f = join $ lift $ demand v (return . f)
342+
demand' v f = join $ lift $ demand v (pure . f)
343343

344344
fromValue' :: (FromValue a m (NValue' t f m (NValue t f m)), MonadNix e t f m) => NValue t f m -> WithStringContextT m a
345345
fromValue' = lift . fromValue
346346

347347
withFrame' :: (Framed e m, Exception s) => NixLevel -> s -> WithStringContextT m a -> WithStringContextT m a
348-
withFrame' level f = join . lift . withFrame level f . return
348+
withFrame' level f = join . lift . withFrame level f . pure
349349

350350
-- shortcuts to get the (forced) value of an AttrSet field
351351

@@ -356,7 +356,7 @@ buildDerivationWithContext drvAttrs = do
356356
Just v -> withFrame' Info (ErrorCall $ "While evaluating attribute '" <> show n <> "'") $
357357
fromValue' v >>= f
358358

359-
getAttrOr n d f = getAttrOr' n (return d) f
359+
getAttrOr n d f = getAttrOr' n (pure d) f
360360

361361
getAttr n = getAttrOr' n (throwError $ ErrorCall $ "Required attribute '" <> show n <> "' not found.")
362362

@@ -370,22 +370,22 @@ buildDerivationWithContext drvAttrs = do
370370
when (Text.length name > 211) $ failWith "must be no longer than 211 characters"
371371
when (Text.any invalid name) $ failWith "contains some invalid character"
372372
when (".drv" `Text.isSuffixOf` name) $ failWith "is not allowed to end in '.drv'"
373-
return name
373+
pure name
374374

375375
extractNoCtx :: MonadNix e t f m => NixString -> WithStringContextT m Text
376376
extractNoCtx ns = case getStringNoContext ns of
377377
Nothing -> lift $ throwError $ ErrorCall $ "The string " <> show ns <> " is not allowed to have a context."
378-
Just v -> return v
378+
Just v -> pure v
379379

380380
assertNonNull :: MonadNix e t f m => Text -> WithStringContextT m Text
381381
assertNonNull t = do
382382
when (Text.null t) $ lift $ throwError $ ErrorCall "Value must not be empty"
383-
return t
383+
pure t
384384

385385
parseHashMode :: MonadNix e t f m => Text -> WithStringContextT m HashMode
386386
parseHashMode = \case
387-
"flat" -> return Flat
388-
"recursive" -> return Recursive
387+
"flat" -> pure Flat
388+
"recursive" -> pure Recursive
389389
other -> lift $ throwError $ ErrorCall $ "Hash mode " <> show other <> " is not valid. It must be either 'flat' or 'recursive'"
390390

391391
-- Other helpers

src/Nix/Fresh.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -90,9 +90,9 @@ instance MonadAtomicRef (ST s) where
9090
v <- readRef r
9191
let (a, b) = f v
9292
writeRef r a
93-
return b
93+
pure b
9494
atomicModifyRef' r f = do
9595
v <- readRef r
9696
let (a, b) = f v
9797
writeRef r $! a
98-
return b
98+
pure b

src/Nix/Fresh/Basic.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -43,10 +43,10 @@ instance (MonadEffects t f m, MonadDataContext f m)
4343
importPath path = do
4444
i <- FreshIdT ask
4545
p <- lift $ importPath @t @f @m path
46-
return $ liftNValue (runFreshIdT i) p
46+
pure $ liftNValue (runFreshIdT i) p
4747
pathToDefaultNix = lift . pathToDefaultNix @t @f @m
4848
derivationStrict v = do
4949
i <- FreshIdT ask
5050
p <- lift $ derivationStrict @t @f @m $ unliftNValue (runFreshIdT i) v
51-
return $ liftNValue (runFreshIdT i) p
51+
pure $ liftNValue (runFreshIdT i) p
5252
traceEffect = lift . traceEffect @t @f @m

src/Nix/Lint.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -202,12 +202,12 @@ merge context = go
202202
mergeFunctions pl nl fl pr fr xs ys = do
203203
m <- sequenceA $ M.intersectionWith
204204
(\i j -> i >>= \i' -> j >>= \j' -> case (i', j') of
205-
(Nothing, Nothing) -> return $ pure Nothing
205+
(Nothing, Nothing) -> pure $ pure Nothing
206206
(_, Nothing) -> pure Nothing
207207
(Nothing, _) -> pure Nothing
208208
(Just i'', Just j'') ->
209209
pure . pure <$> unify context i'' j'')
210-
(return <$> pl) (return <$> pr)
210+
(pure <$> pl) (pure <$> pr)
211211
let Just m' = sequenceA $ M.filter isJust m
212212
if M.null m'
213213
then go xs ys

src/Nix/Parser.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -608,7 +608,7 @@ nixOperators selector =
608608
-- Postfix $ do
609609
-- sel <- seldot *> selector
610610
-- mor <- optional (reserved "or" *> term)
611-
-- return $ \x -> nSelectLoc x sel mor) ]
611+
-- pure $ \x -> nSelectLoc x sel mor) ]
612612

613613
{- 2 -}
614614
[ ( NBinaryDef " " NApp NAssocLeft

src/Nix/Reduce.hs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -113,7 +113,7 @@ staticImport pann path = do
113113
local (const (pure path, emptyScopes @m @NExprLoc)) $ do
114114
x'' <- foldFix reduce x'
115115
modify (\(a, b) -> (M.insert path x'' a, b))
116-
return x''
116+
pure x''
117117

118118
-- gatherNames :: NExprLoc -> HashSet VarName
119119
-- gatherNames = foldFix $ \case
@@ -148,10 +148,10 @@ reduce (NSym_ ann var) = lookupVar var <&> \case
148148
-- | Reduce binary and integer negation.
149149
reduce (NUnary_ uann op arg) = arg >>= \x -> case (op, x) of
150150
(NNeg, Fix (NConstant_ cann (NInt n))) ->
151-
return $ Fix $ NConstant_ cann (NInt (negate n))
151+
pure $ Fix $ NConstant_ cann (NInt (negate n))
152152
(NNot, Fix (NConstant_ cann (NBool b))) ->
153-
return $ Fix $ NConstant_ cann (NBool (not b))
154-
_ -> return $ Fix $ NUnary_ uann op x
153+
pure $ Fix $ NConstant_ cann (NBool (not b))
154+
_ -> pure $ Fix $ NUnary_ uann op x
155155

156156
-- | Reduce function applications.
157157
--
@@ -163,7 +163,7 @@ reduce (NBinary_ bann NApp fun arg) = fun >>= \case
163163
f@(Fix (NSym_ _ "import")) -> arg >>= \case
164164
-- Fix (NEnvPath_ pann origPath) -> staticImport pann origPath
165165
Fix (NLiteralPath_ pann origPath) -> staticImport pann origPath
166-
v -> return $ Fix $ NBinary_ bann NApp f v
166+
v -> pure $ Fix $ NBinary_ bann NApp f v
167167

168168
Fix (NAbs_ _ (Param name) body) -> do
169169
x <- arg
@@ -177,7 +177,7 @@ reduce (NBinary_ bann op larg rarg) = do
177177
rval <- rarg
178178
case (op, lval, rval) of
179179
(NPlus, Fix (NConstant_ ann (NInt x)), Fix (NConstant_ _ (NInt y))) ->
180-
return $ Fix (NConstant_ ann (NInt (x + y)))
180+
pure $ Fix (NConstant_ ann (NInt (x + y)))
181181
_ -> pure $ Fix $ NBinary_ bann op lval rval
182182

183183
-- | Reduce a select on a Set by substituting the set to the selected value.
@@ -411,7 +411,7 @@ reducingEvalExpr eval mpath expr = do
411411
eres <- catch (Right <$> foldFix (addEvalFlags eval) expr') (pure . Left)
412412
opts :: Options <- asks (view hasLens)
413413
expr'' <- pruneTree opts expr'
414-
return (fromMaybe nNull expr'', eres)
414+
pure (fromMaybe nNull expr'', eres)
415415
where addEvalFlags k (FlaggedF (b, x)) = liftIO (writeIORef b True) *> k x
416416

417417
instance Monad m => Scoped NExprLoc (Reducer m) where

src/Nix/Render.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -92,14 +92,14 @@ renderLocation (SrcSpan (SourcePos file begLine begCol) (SourcePos file' endLine
9292
if exist
9393
then do
9494
txt <- sourceContext file begLine begCol endLine endCol msg
95-
return
95+
pure
9696
$ vsep
9797
[ "In file "
9898
<> errorContext file begLine begCol endLine endCol
9999
<> ":"
100100
, txt
101101
]
102-
else return msg
102+
else pure msg
103103
renderLocation (SrcSpan beg end) msg =
104104
fail
105105
$ "Don't know how to render range from "

0 commit comments

Comments
 (0)