Skip to content

Commit 558701d

Browse files
committed
map -> fmap
Allow not only literal lists. This for example should allow NonEmpty lists at least. Also do not think I do this things on a whim. I postphoned the refactors from map, (++), until I understand the underlying GHC Haskell processes & performance better. I did some research on: is there a reason to use map over fmap, and are the performance reasons? In short - there is 0 information on why some people use `map` over `fmap`, there are no reports of performance reasons. Well, I know that there is a possibility of a minor type class interface compilation & runtime use cost. But I think GHC is good enough to infer zero cost for the concrete list type for which `map` gets used. And overall we not did thorough profiling/perfommans walkthrough so far. I am sure that use of standard fmap for code flexibility is not a bottleneck in the design, I've seen some performance problems design has. And we not even did the profiling to do inlining and specialize work yet. It is more effective to keep using `fmap`, and supply specialization, which allows to keep the code polymorhic, portable to write for and effective in performance.
1 parent ffa62f8 commit 558701d

File tree

19 files changed

+59
-60
lines changed

19 files changed

+59
-60
lines changed

main/Repl.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -348,7 +348,7 @@ completeFunc reversedPrev word
348348
-- Commands
349349
| reversedPrev == ":"
350350
= pure . listCompletion
351-
$ map helpOptionName (helpOptions :: HelpOptions e t f m)
351+
$ fmap helpOptionName (helpOptions :: HelpOptions e t f m)
352352

353353
-- Files
354354
| any (`Data.List.isPrefixOf` word) [ "/", "./", "../", "~/" ]
@@ -364,7 +364,7 @@ completeFunc reversedPrev word
364364
Just binding -> do
365365
candidates <- lift $ algebraicComplete subFields binding
366366
pure
367-
$ map notFinished
367+
$ fmap notFinished
368368
$ listCompletion (Data.Text.unpack . (var <>) <$> candidates)
369369

370370
-- Builtins, context variables
@@ -381,7 +381,7 @@ completeFunc reversedPrev word
381381
++ (Data.Text.unpack <$> shortBuiltins)
382382

383383
where
384-
listCompletion = map simpleCompletion . filter (word `Data.List.isPrefixOf`)
384+
listCompletion = fmap simpleCompletion . filter (word `Data.List.isPrefixOf`)
385385

386386
notFinished x = x { isFinished = False }
387387

@@ -508,7 +508,7 @@ renderSetOptions :: [HelpSetOption] -> Doc ()
508508
renderSetOptions so =
509509
Prettyprinter.indent 4
510510
$ Prettyprinter.vsep
511-
$ flip map so
511+
$ flip fmap so
512512
$ \h ->
513513
Prettyprinter.pretty (helpSetOptionName h)
514514
<+> helpSetOptionSyntax h

src/Nix.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -107,7 +107,7 @@ evaluateExpression
107107
-> m a
108108
evaluateExpression mpath evaluator handler expr = do
109109
opts :: Options <- asks (view hasLens)
110-
args <- traverse (traverse eval') $ map (second parseArg) (arg opts) ++ map
110+
args <- traverse (traverse eval') $ fmap (second parseArg) (arg opts) ++ fmap
111111
(second mkStr)
112112
(argstr opts)
113113
evaluator mpath expr >>= \f -> demand f $ \f' ->

src/Nix/Builtins.hs

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -102,7 +102,7 @@ withNixContext
102102
withNixContext mpath action = do
103103
base <- builtins
104104
opts :: Options <- asks (view hasLens)
105-
let i = nvList $ map
105+
let i = nvList $ fmap
106106
( nvStr
107107
. makeNixStringWithoutContext
108108
. Text.pack
@@ -122,10 +122,10 @@ builtins = do
122122
lst <- ([("builtins", ref)] ++) <$> topLevelBuiltins
123123
pushScope (M.fromList lst) currentScopes
124124
where
125-
buildMap = M.fromList . map mapping <$> builtinsList
126-
topLevelBuiltins = map mapping <$> fullBuiltinsList
125+
buildMap = M.fromList . fmap mapping <$> builtinsList
126+
topLevelBuiltins = fmap mapping <$> fullBuiltinsList
127127

128-
fullBuiltinsList = map go <$> builtinsList
128+
fullBuiltinsList = fmap go <$> builtinsList
129129
where
130130
go b@(Builtin TopLevel _) = b
131131
go (Builtin Normal (name, builtin)) =
@@ -322,7 +322,7 @@ foldNixPath f z = do
322322
mDataDir <- getEnvVar "NIX_DATA_DIR"
323323
dataDir <- maybe getDataDir pure mDataDir
324324
foldrM go z
325-
$ map (fromInclude . stringIgnoreContext) dirs
325+
$ fmap (fromInclude . stringIgnoreContext) dirs
326326
++ case mPath of
327327
Nothing -> []
328328
Just str -> uriAwareSplit (Text.pack str)
@@ -538,7 +538,7 @@ splitVersion_ :: MonadNix e t f m => NValue t f m -> m (NValue t f m)
538538
splitVersion_ = fromValue >=> fromStringNoContext >=> \s ->
539539
pure
540540
$ nvList
541-
$ flip map (splitVersion s)
541+
$ flip fmap (splitVersion s)
542542
$ nvStr
543543
. makeNixStringWithoutContext
544544
. versionComponentToString
@@ -615,7 +615,7 @@ match_ pat str = fromValue pat >>= fromStringNoContext >>= \p ->
615615
otherwise = toValue $ makeNixStringWithoutContext t
616616
case matchOnceText re (encodeUtf8 s) of
617617
Just ("", sarr, "") -> do
618-
let s = map fst (elems sarr)
618+
let s = fmap fst (elems sarr)
619619
nvList <$> traverse (mkMatch . decodeUtf8)
620620
(if length s > 1 then tail s else s)
621621
_ -> pure $ nvConstant NNull
@@ -677,7 +677,7 @@ attrNames =
677677
fromValue @(AttrSet (NValue t f m))
678678
>=> fmap getDeeper
679679
. toValue
680-
. map makeNixStringWithoutContext
680+
. fmap makeNixStringWithoutContext
681681
. sort
682682
. M.keys
683683

@@ -932,7 +932,7 @@ replaceStrings
932932
replaceStrings tfrom tto ts = fromValue (Deeper tfrom) >>= \(nsFrom :: [NixString]) ->
933933
fromValue (Deeper tto) >>= \(nsTo :: [NixString]) ->
934934
fromValue ts >>= \(ns :: NixString) -> do
935-
let from = map stringIgnoreContext nsFrom
935+
let from = fmap stringIgnoreContext nsFrom
936936
when (length nsFrom /= length nsTo)
937937
$ throwError
938938
$ ErrorCall
@@ -1432,7 +1432,7 @@ partition_ f = fromValue @[NValue t f m] >=> \l -> do
14321432
let match t = f `callFunc` t >>= fmap (, t) . fromValue
14331433
selection <- traverse match l
14341434
let (right, wrong) = partition fst selection
1435-
let makeSide = nvList . map snd
1435+
let makeSide = nvList . fmap snd
14361436
toValue @(AttrSet (NValue t f m))
14371437
$ M.fromList [("right", makeSide right), ("wrong", makeSide wrong)]
14381438

src/Nix/Effects/Derivation.hs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -130,24 +130,24 @@ hashDerivationModulo drv@(Derivation {inputs = (inputSrcs, inputDrvs)}) = do
130130
unparseDrv :: Derivation -> Text
131131
unparseDrv (Derivation {..}) = Text.append "Derive" $ parens
132132
[ -- outputs: [("out", "/nix/store/.....-out", "", ""), ...]
133-
list $ flip map (Map.toList outputs) (\(outputName, outputPath) ->
133+
list $ flip fmap (Map.toList outputs) (\(outputName, outputPath) ->
134134
let prefix = if hashMode == Recursive then "r:" else "" in
135135
case mFixed of
136136
Nothing -> parens [s outputName, s outputPath, s "", s ""]
137137
Just (Store.SomeDigest (digest :: Store.Digest hashType)) ->
138138
parens [s outputName, s outputPath, s $ prefix <> Store.algoName @hashType, s $ Store.encodeInBase Store.Base16 digest]
139139
)
140140
, -- inputDrvs
141-
list $ flip map (Map.toList $ snd inputs) (\(path, outs) ->
142-
parens [s path, list $ map s $ sort outs])
141+
list $ flip fmap (Map.toList $ snd inputs) (\(path, outs) ->
142+
parens [s path, list $ fmap s $ sort outs])
143143
, -- inputSrcs
144144
list (map s $ Set.toList $ fst inputs)
145145
, s platform
146146
, s builder
147147
, -- run script args
148-
list $ map s args
148+
list $ fmap s args
149149
, -- env (key value pairs)
150-
list $ flip map (Map.toList env) (\(k, v) ->
150+
list $ flip fmap (Map.toList env) (\(k, v) ->
151151
parens [s k, s v])
152152
]
153153
where
@@ -192,7 +192,7 @@ derivationParser = do
192192
_ <- ")"
193193
eof
194194

195-
let outputs = Map.fromList $ map (\(a, b, _, _) -> (a, b)) fullOutputs
195+
let outputs = Map.fromList $ fmap (\(a, b, _, _) -> (a, b)) fullOutputs
196196
let (mFixed, hashMode) = parseFixed fullOutputs
197197
let name = "" -- FIXME (extract from file path ?)
198198
let useJson = ["__json"] == Map.keys env
@@ -332,7 +332,7 @@ buildDerivationWithContext drvAttrs = do
332332

333333
return $ defaultDerivation { platform, builder, args, env, hashMode, useJson
334334
, name = drvName
335-
, outputs = Map.fromList $ map (\o -> (o, "")) outputs
335+
, outputs = Map.fromList $ fmap (\o -> (o, "")) outputs
336336
, mFixed = mFixedOutput
337337
}
338338
where

src/Nix/Eval.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -257,7 +257,7 @@ evalBinds recursive binds = do
257257
go _ (NamedVar (StaticKey "__overrides" :| []) finalValue pos) =
258258
finalValue >>= fromValue >>= \(o', p') ->
259259
-- jww (2018-05-09): What to do with the key position here?
260-
pure $ map
260+
pure $ fmap
261261
(\(k, v) -> ([k], fromMaybe pos (M.lookup k p'), demand v pure))
262262
(M.toList o')
263263

src/Nix/Expr/Shorthands.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -135,7 +135,7 @@ mkDots e [] = e
135135
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.
138-
Fix (NSelect e (keys' <> map (StaticKey ?? Nothing) keys) x)
138+
Fix (NSelect e (keys' <> fmap (StaticKey ?? Nothing) keys) x)
139139
mkDots e keys = Fix $ NSelect e (map (StaticKey ?? Nothing) keys) Nothing
140140
-}
141141

src/Nix/Expr/Strings.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -62,7 +62,7 @@ stripIndent xs =
6262
Indented minIndent
6363
. removePlainEmpty
6464
. mergePlain
65-
. map snd
65+
. fmap snd
6666
. dropWhileEnd cleanup
6767
. (\ys -> zip
6868
(map
@@ -78,11 +78,11 @@ stripIndent xs =
7878
$ ls'
7979
where
8080
ls = stripEmptyOpening $ splitLines xs
81-
ls' = map (dropSpaces minIndent) ls
81+
ls' = fmap (dropSpaces minIndent) ls
8282

8383
minIndent = case stripEmptyLines ls of
8484
[] -> 0
85-
nonEmptyLs -> minimum $ map (countSpaces . mergePlain) nonEmptyLs
85+
nonEmptyLs -> minimum $ fmap (countSpaces . mergePlain) nonEmptyLs
8686

8787
stripEmptyLines = filter $ \case
8888
[Plain t] -> not $ T.null $ T.strip t
@@ -109,7 +109,7 @@ escapeCodes =
109109
[('\n', 'n'), ('\r', 'r'), ('\t', 't'), ('\\', '\\'), ('$', '$'), ('"', '"')]
110110

111111
fromEscapeCode :: Char -> Maybe Char
112-
fromEscapeCode = (`lookup` map swap escapeCodes)
112+
fromEscapeCode = (`lookup` fmap swap escapeCodes)
113113

114114
toEscapeCode :: Char -> Maybe Char
115115
toEscapeCode = (`lookup` escapeCodes)

src/Nix/Fresh/Basic.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -36,7 +36,7 @@ instance (MonadEffects t f m, MonadDataContext f m)
3636
findEnvPath = lift . findEnvPath @t @f @m
3737
findPath vs path = do
3838
i <- FreshIdT ask
39-
let vs' = map (unliftNValue (runFreshIdT i)) vs
39+
let vs' = fmap (unliftNValue (runFreshIdT i)) vs
4040
lift $ findPath @t @f @m vs' path
4141
importPath path = do
4242
i <- FreshIdT ask

src/Nix/Parser.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -67,8 +67,7 @@ import qualified Data.HashSet as HashSet
6767
import Data.List.NonEmpty ( NonEmpty(..) )
6868
import qualified Data.List.NonEmpty as NE
6969
import qualified Data.Map as Map
70-
import Data.Text hiding ( map
71-
, foldr1
70+
import Data.Text hiding ( foldr1
7271
, concat
7372
, concatMap
7473
, zipWith
@@ -94,7 +93,7 @@ infixl 3 <+>
9493
---------------------------------------------------------------------------------
9594

9695
nixExpr :: Parser NExprLoc
97-
nixExpr = makeExprParser nixTerm $ map (map snd) (nixOperators nixSelector)
96+
nixExpr = makeExprParser nixTerm $ fmap (fmap snd) (nixOperators nixSelector)
9897

9998
antiStart :: Parser Text
10099
antiStart = symbol "${" <?> show ("${" :: String)

src/Nix/Pretty.hs

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -116,7 +116,7 @@ wrapPath op sub = if wasPath sub
116116
else wrapParens op sub
117117

118118
prettyString :: NString (NixDoc ann) -> Doc ann
119-
prettyString (DoubleQuoted parts) = dquotes . hcat . map prettyPart $ parts
119+
prettyString (DoubleQuoted parts) = dquotes . hcat . fmap prettyPart $ parts
120120
where
121121
prettyPart (Plain t) = pretty . concatMap escape . unpack $ t
122122
prettyPart EscapedNewline = "''\\n"
@@ -127,11 +127,11 @@ prettyString (Indented _ parts) = group $ nest 2 $ vcat
127127
[dsquote, content, dsquote]
128128
where
129129
dsquote = squote <> squote
130-
content = vsep . map prettyLine . stripLastIfEmpty . splitLines $ parts
130+
content = vsep . fmap prettyLine . stripLastIfEmpty . splitLines $ parts
131131
stripLastIfEmpty = reverse . f . reverse where
132132
f ([Plain t] : xs) | Text.null (strip t) = xs
133133
f xs = xs
134-
prettyLine = hcat . map prettyPart
134+
prettyLine = hcat . fmap prettyPart
135135
prettyPart (Plain t) =
136136
pretty . unpack . replace "${" "''${" . replace "''" "'''" $ t
137137
prettyPart EscapedNewline = "\\n"
@@ -176,7 +176,7 @@ prettyKeyName (DynamicKey key) = runAntiquoted
176176
key
177177

178178
prettySelector :: NAttrPath (NixDoc ann) -> Doc ann
179-
prettySelector = hcat . punctuate dot . map prettyKeyName . NE.toList
179+
prettySelector = hcat . punctuate dot . fmap prettyKeyName . NE.toList
180180

181181
prettyAtom :: NAtom -> NixDoc ann
182182
prettyAtom atom = simpleExpr $ pretty $ unpack $ atomText atom
@@ -225,23 +225,23 @@ exprFNixDoc = \case
225225
$ nest 2
226226
$ vsep
227227
$ concat
228-
$ [[lbracket], map (wrapParens appOpNonAssoc) xs, [rbracket]]
228+
$ [[lbracket], fmap (wrapParens appOpNonAssoc) xs, [rbracket]]
229229
NSet NNonRecursive [] -> simpleExpr $ lbrace <> rbrace
230230
NSet NNonRecursive xs ->
231231
simpleExpr
232232
$ group
233233
$ nest 2
234234
$ vsep
235235
$ concat
236-
$ [[lbrace], map prettyBind xs, [rbrace]]
236+
$ [[lbrace], fmap prettyBind xs, [rbrace]]
237237
NSet NRecursive [] -> simpleExpr $ recPrefix <> lbrace <> rbrace
238238
NSet NRecursive xs ->
239239
simpleExpr
240240
$ group
241241
$ nest 2
242242
$ vsep
243243
$ concat
244-
$ [[recPrefix <> lbrace], map prettyBind xs, [rbrace]]
244+
$ [[recPrefix <> lbrace], fmap prettyBind xs, [rbrace]]
245245
NAbs args body ->
246246
leastPrecedence
247247
$ nest 2
@@ -357,7 +357,7 @@ prettyNValueProv v = do
357357
$ parens
358358
$ mconcat
359359
$ "from: "
360-
: map (prettyOriginExpr . _originExpr) ps
360+
: fmap (prettyOriginExpr . _originExpr) ps
361361
]
362362

363363
prettyNThunk
@@ -379,7 +379,7 @@ prettyNThunk t = do
379379
$ parens
380380
$ mconcat
381381
$ "thunk from: "
382-
: map (prettyOriginExpr . _originExpr) ps
382+
: fmap (prettyOriginExpr . _originExpr) ps
383383
]
384384

385385
-- | This function is used only by the testing code.

0 commit comments

Comments
 (0)