Skip to content

Commit fa7aab2

Browse files
committed
remaining map -> fmap
1 parent 6383f1f commit fa7aab2

File tree

4 files changed

+8
-8
lines changed

4 files changed

+8
-8
lines changed

main/Repl.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -100,7 +100,7 @@ main' iniVal = initState iniVal >>= \s -> flip evalStateT s
100100

101101
rcFile = do
102102
f <- liftIO $ Data.Text.IO.readFile ".hnixrc" `catch` handleMissing
103-
forM_ (map (words . Data.Text.unpack) $ Data.Text.lines f) $ \case
103+
forM_ (fmap (words . Data.Text.unpack) $ Data.Text.lines f) $ \case
104104
((prefix:command) : xs) | prefix == commandPrefix -> do
105105
let arguments = unwords xs
106106
optMatcher command options arguments

tests/NixLanguageTests.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -158,7 +158,7 @@ assertEval _opts files = do
158158
Opts.execParserPure
159159
Opts.defaultPrefs
160160
(nixOptionsInfo time)
161-
(fixup (map Text.unpack (Text.splitOn " " flags')))
161+
(fixup (fmap Text.unpack (Text.splitOn " " flags')))
162162
of
163163
Opts.Failure err ->
164164
errorWithoutStackTrace
@@ -171,7 +171,7 @@ assertEval _opts files = do
171171
_ -> assertFailure $ "Unknown test type " ++ show files
172172
where
173173
name =
174-
"data/nix/tests/lang/" ++ the (map (takeFileName . dropExtensions) files)
174+
"data/nix/tests/lang/" ++ the (fmap (takeFileName . dropExtensions) files)
175175

176176
fixup ("--arg" : x : y : rest) = "--arg" : (x ++ "=" ++ y) : fixup rest
177177
fixup ("--argstr" : x : y : rest) = "--argstr" : (x ++ "=" ++ y) : fixup rest

tests/ParserTests.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -122,7 +122,7 @@ case_inherit_selector = do
122122
case_int_list = assertParseText "[1 2 3]" $ Fix $ NList
123123
[ mkInt i | i <- [1,2,3] ]
124124

125-
case_int_null_list = assertParseText "[1 2 3 null 4]" $ Fix (NList (map (Fix . NConstant) [NInt 1, NInt 2, NInt 3, NNull, NInt 4]))
125+
case_int_null_list = assertParseText "[1 2 3 null 4]" $ Fix (NList (fmap (Fix . NConstant) [NInt 1, NInt 2, NInt 3, NNull, NInt 4]))
126126

127127
case_mixed_list = do
128128
assertParseText "[{a = 3;}.a (if true then null else false) null false 4 [] c.d or null]" $ Fix $ NList

tests/PrettyParseTests.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -148,16 +148,16 @@ normalize = foldFix $ \case
148148
NConstant (NFloat n) | n < 0 ->
149149
Fix (NUnary NNeg (Fix (NConstant (NFloat (negate n)))))
150150

151-
NSet recur binds -> Fix (NSet recur (map normBinding binds))
152-
NLet binds r -> Fix (NLet (map normBinding binds) r)
151+
NSet recur binds -> Fix (NSet recur (fmap normBinding binds))
152+
NLet binds r -> Fix (NLet (fmap normBinding binds) r)
153153

154154
NAbs params r -> Fix (NAbs (normParams params) r)
155155

156156
r -> Fix r
157157

158158
where
159159
normBinding (NamedVar path r pos) = NamedVar (NE.map normKey path) r pos
160-
normBinding (Inherit mr names pos) = Inherit mr (map normKey names) pos
160+
normBinding (Inherit mr names pos) = Inherit mr (fmap normKey names) pos
161161

162162
normKey (DynamicKey quoted) = DynamicKey (normAntiquotedString quoted)
163163
normKey (StaticKey name ) = StaticKey name
@@ -220,7 +220,7 @@ prop_prettyparse p = do
220220
normalise = unlines . fmap (reverse . dropWhile isSpace . reverse) . lines
221221

222222
ldiff :: String -> String -> [Diff [String]]
223-
ldiff s1 s2 = getDiff (map (: []) (lines s1)) (map (: []) (lines s2))
223+
ldiff s1 s2 = getDiff (fmap (: []) (lines s1)) (fmap (: []) (lines s2))
224224

225225
tests :: TestLimit -> TestTree
226226
tests n = testProperty "Pretty/Parse Property" $ withTests n $ property $ do

0 commit comments

Comments
 (0)