Skip to content

Commit c5d04c3

Browse files
committed
additional map -> fmap
1 parent 753dfc6 commit c5d04c3

File tree

13 files changed

+37
-37
lines changed

13 files changed

+37
-37
lines changed

src/Nix/Builtins.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -636,7 +636,7 @@ split_ pat str = fromValue pat >>= fromStringNoContext >>= \p ->
636636
let re = makeRegex (encodeUtf8 p) :: Regex
637637
haystack = encodeUtf8 s
638638
pure $ nvList $ splitMatches 0
639-
(map elems $ matchAllText re haystack)
639+
(fmap elems $ matchAllText re haystack)
640640
haystack
641641

642642
splitMatches
@@ -656,7 +656,7 @@ splitMatches numDropped (((_, (start, len)) : captures) : mts) haystack =
656656
where
657657
relStart = max 0 start - numDropped
658658
(before, rest) = B.splitAt relStart haystack
659-
caps = nvList (map f captures)
659+
caps = nvList (fmap f captures)
660660
f (a, (s, _)) = if s < 0 then nvConstant NNull else thunkStr a
661661

662662
thunkStr :: Applicative f => ByteString -> NValue t f m
@@ -718,7 +718,7 @@ mapAttrs_ f xs = fromValue @(AttrSet (NValue t f m)) xs >>= \aset -> do
718718
$ withFrame Debug (ErrorCall "While applying f in mapAttrs:\n")
719719
$ callFunc ?? value
720720
=<< callFunc f (nvStr (makeNixStringWithoutContext key))
721-
toValue . M.fromList . zip (map fst pairs) $ values
721+
toValue . M.fromList . zip (fmap fst pairs) $ values
722722

723723
filter_
724724
:: forall e t f m
@@ -1393,7 +1393,7 @@ exec_ xs = do
13931393
-- TODO Still need to do something with the context here
13941394
-- See prim_exec in nix/src/libexpr/primops.cc
13951395
-- Requires the implementation of EvalState::realiseContext
1396-
exec (map (Text.unpack . stringIgnoreContext) xs)
1396+
exec (fmap (Text.unpack . stringIgnoreContext) xs)
13971397

13981398
fetchurl
13991399
:: forall e t f m . MonadNix e t f m => NValue t f m -> m (NValue t f m)

src/Nix/Effects/Derivation.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -141,7 +141,7 @@ unparseDrv (Derivation {..}) = Text.append "Derive" $ parens
141141
list $ flip fmap (Map.toList $ snd inputs) (\(path, outs) ->
142142
parens [s path, list $ fmap s $ sort outs])
143143
, -- inputSrcs
144-
list (map s $ Set.toList $ fst inputs)
144+
list (fmap s $ Set.toList $ fst inputs)
145145
, s platform
146146
, s builder
147147
, -- run script args

src/Nix/Exec.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -173,13 +173,13 @@ instance MonadNix e t f m => MonadEval (NValue t f m) m where
173173
evalError @(NValue t f m)
174174
$ ErrorCall
175175
$ "Inheriting unknown attribute: "
176-
<> intercalate "." (map Text.unpack (NE.toList ks))
176+
<> intercalate "." (fmap Text.unpack (NE.toList ks))
177177

178178
attrMissing ks (Just s) =
179179
evalError @(NValue t f m)
180180
$ ErrorCall
181181
$ "Could not look up attribute "
182-
<> intercalate "." (map Text.unpack (NE.toList ks))
182+
<> intercalate "." (fmap Text.unpack (NE.toList ks))
183183
<> " in "
184184
<> show (prettyNValue s)
185185

src/Nix/Expr/Shorthands.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -136,7 +136,7 @@ mkDots (Fix (NSelect e keys' x)) keys =
136136
-- Special case: if the expression in the first argument is already
137137
-- a dotted expression, just extend it.
138138
Fix (NSelect e (keys' <> fmap (StaticKey ?? Nothing) keys) x)
139-
mkDots e keys = Fix $ NSelect e (map (StaticKey ?? Nothing) keys) Nothing
139+
mkDots e keys = Fix $ NSelect e (fmap (StaticKey ?? Nothing) keys) Nothing
140140
-}
141141

142142
-- | An `inherit` clause without an expression to pull from.
@@ -174,19 +174,19 @@ modifyFunctionBody f (Fix e) = case e of
174174

175175
-- | A let statement with multiple assignments.
176176
letsE :: [(Text, NExpr)] -> NExpr -> NExpr
177-
letsE pairs = Fix . NLet (map (uncurry bindTo) pairs)
177+
letsE pairs = Fix . NLet (fmap (uncurry bindTo) pairs)
178178

179179
-- | Wrapper for a single-variable @let@.
180180
letE :: Text -> NExpr -> NExpr -> NExpr
181181
letE varName varExpr = letsE [(varName, varExpr)]
182182

183183
-- | Make an attribute set (non-recursive).
184184
attrsE :: [(Text, NExpr)] -> NExpr
185-
attrsE pairs = Fix $ NSet NNonRecursive (map (uncurry bindTo) pairs)
185+
attrsE pairs = Fix $ NSet NNonRecursive (fmap (uncurry bindTo) pairs)
186186

187187
-- | Make an attribute set (recursive).
188188
recAttrsE :: [(Text, NExpr)] -> NExpr
189-
recAttrsE pairs = Fix $ NSet NRecursive (map (uncurry bindTo) pairs)
189+
recAttrsE pairs = Fix $ NSet NRecursive (fmap (uncurry bindTo) pairs)
190190

191191
-- | Logical negation.
192192
mkNot :: NExpr -> NExpr

src/Nix/Expr/Types.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -609,8 +609,8 @@ ekey _ _ f e = fromMaybe e <$> f Nothing
609609
stripPositionInfo :: NExpr -> NExpr
610610
stripPositionInfo = transport phi
611611
where
612-
phi (NSet recur binds) = NSet recur (map go binds)
613-
phi (NLet binds body) = NLet (map go binds) body
612+
phi (NSet recur binds) = NSet recur (fmap go binds)
613+
phi (NLet binds body) = NLet (fmap go binds) body
614614
phi x = x
615615

616616
go (NamedVar path r _pos) = NamedVar path r nullPos

src/Nix/Lint.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -276,13 +276,13 @@ instance MonadLint e m => MonadEval (Symbolic m) m where
276276
evalError @(Symbolic m)
277277
$ ErrorCall
278278
$ "Inheriting unknown attribute: "
279-
<> intercalate "." (map Text.unpack (NE.toList ks))
279+
<> intercalate "." (fmap Text.unpack (NE.toList ks))
280280

281281
attrMissing ks (Just s) =
282282
evalError @(Symbolic m)
283283
$ ErrorCall
284284
$ "Could not look up attribute "
285-
<> intercalate "." (map Text.unpack (NE.toList ks))
285+
<> intercalate "." (fmap Text.unpack (NE.toList ks))
286286
<> " in "
287287
<> show s
288288

src/Nix/Pretty.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -149,7 +149,7 @@ prettyParamSet args var = encloseSep
149149
(lbrace <> space)
150150
(align (space <> rbrace))
151151
sep
152-
(map prettySetArg args <> prettyVariadic)
152+
(fmap prettySetArg args <> prettyVariadic)
153153
where
154154
prettySetArg (n, maybeDef) = case maybeDef of
155155
Nothing -> pretty (unpack n)
@@ -161,7 +161,7 @@ prettyBind :: Binding (NixDoc ann) -> Doc ann
161161
prettyBind (NamedVar n v _p) =
162162
prettySelector n <+> equals <+> withoutParens v <> semi
163163
prettyBind (Inherit s ns _p) =
164-
"inherit" <+> scope <> align (fillSep (map prettyKeyName ns)) <> semi
164+
"inherit" <+> scope <> align (fillSep (fmap prettyKeyName ns)) <> semi
165165
where scope = maybe mempty ((<> space) . parens . withoutParens) s
166166

167167
prettyKeyName :: NKeyName (NixDoc ann) -> Doc ann
@@ -289,7 +289,7 @@ exprFNixDoc = \case
289289
$ group
290290
$ vsep
291291
$ [ "let"
292-
, indent 2 (vsep (map prettyBind binds))
292+
, indent 2 (vsep (fmap prettyBind binds))
293293
, "in" <+> withoutParens body
294294
]
295295
NIf cond trueBody falseBody ->

src/Nix/Reduce.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -313,10 +313,10 @@ pruneTree opts = foldFixM $ \(FlaggedF (b, Compose x)) -> do
313313
NAbs params (Just body) -> Just $ NAbs (pruneParams params) body
314314

315315
NList l | reduceLists opts -> Just $ NList (catMaybes l)
316-
| otherwise -> Just $ NList (map (fromMaybe nNull) l)
316+
| otherwise -> Just $ NList (fmap (fromMaybe nNull) l)
317317
NSet recur binds
318318
| reduceSets opts -> Just $ NSet recur (mapMaybe sequence binds)
319-
| otherwise -> Just $ NSet recur (map (fmap (fromMaybe nNull)) binds)
319+
| otherwise -> Just $ NSet recur (fmap (fmap (fromMaybe nNull)) binds)
320320

321321
NLet binds (Just body@(Fix (Compose (Ann _ x)))) ->
322322
Just $ case mapMaybe pruneBinding binds of
@@ -386,10 +386,10 @@ pruneTree opts = foldFixM $ \(FlaggedF (b, Compose x)) -> do
386386
pruneParams (Param n) = Param n
387387
pruneParams (ParamSet xs b n)
388388
| reduceSets opts = ParamSet
389-
(map (second (maybe (Just nNull) (Just . fromMaybe nNull))) xs)
389+
(fmap (second (maybe (Just nNull) (Just . fromMaybe nNull))) xs)
390390
b
391391
n
392-
| otherwise = ParamSet (map (second (fmap (fromMaybe nNull))) xs) b n
392+
| otherwise = ParamSet (fmap (second (fmap (fromMaybe nNull))) xs) b n
393393

394394
pruneBinding :: Binding (Maybe NExprLoc) -> Maybe (Binding NExprLoc)
395395
pruneBinding (NamedVar _ Nothing _) = Nothing
@@ -398,7 +398,7 @@ pruneTree opts = foldFixM $ \(FlaggedF (b, Compose x)) -> do
398398
pruneBinding (Inherit _ [] _) = Nothing
399399
pruneBinding (Inherit (join -> Nothing) _ _) = Nothing
400400
pruneBinding (Inherit (join -> m) xs pos) =
401-
Just (Inherit m (map pruneKeyName xs) pos)
401+
Just (Inherit m (fmap pruneKeyName xs) pos)
402402

403403
reducingEvalExpr
404404
:: (Framed e m, Has e Options, Exception r, MonadCatch m, MonadIO m)

src/Nix/Render.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -127,6 +127,6 @@ sourceContext path (unPos -> begLine) (unPos -> _begCol) (unPos -> endLine) (unP
127127
pad n | read n == begLine = "==> " <> n
128128
| otherwise = " " <> n
129129
ls' = zipWith (<+>)
130-
(map (pretty . pad) nums')
131-
(map ("| " <+>) ls)
130+
(fmap (pretty . pad) nums')
131+
(fmap ("| " <+>) ls)
132132
pure $ vsep $ ls' <> [msg]

src/Nix/String.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -221,6 +221,6 @@ intercalateNixString _ [] = mempty
221221
intercalateNixString _ [ns] = ns
222222
intercalateNixString sep nss = NixString contents ctx
223223
where
224-
contents = Text.intercalate (nsContents sep) (map nsContents nss)
224+
contents = Text.intercalate (nsContents sep) (fmap nsContents nss)
225225
ctx = S.unions (nsContext sep : fmap nsContext nss)
226226

0 commit comments

Comments
 (0)