Skip to content

Commit

Permalink
remaining map -> fmap
Browse files Browse the repository at this point in the history
  • Loading branch information
Anton-Latukha committed Feb 8, 2021
1 parent 0da2293 commit 3b8845f
Show file tree
Hide file tree
Showing 4 changed files with 8 additions and 8 deletions.
2 changes: 1 addition & 1 deletion main/Repl.hs
Original file line number Diff line number Diff line change
Expand Up @@ -100,7 +100,7 @@ main' iniVal = initState iniVal >>= \s -> flip evalStateT s

rcFile = do
f <- liftIO $ Data.Text.IO.readFile ".hnixrc" `catch` handleMissing
forM_ (map (words . Data.Text.unpack) $ Data.Text.lines f) $ \case
forM_ (fmap (words . Data.Text.unpack) $ Data.Text.lines f) $ \case
((prefix:command) : xs) | prefix == commandPrefix -> do
let arguments = unwords xs
optMatcher command options arguments
Expand Down
4 changes: 2 additions & 2 deletions tests/NixLanguageTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -158,7 +158,7 @@ assertEval _opts files = do
Opts.execParserPure
Opts.defaultPrefs
(nixOptionsInfo time)
(fixup (map Text.unpack (Text.splitOn " " flags')))
(fixup (fmap Text.unpack (Text.splitOn " " flags')))
of
Opts.Failure err ->
errorWithoutStackTrace
Expand All @@ -171,7 +171,7 @@ assertEval _opts files = do
_ -> assertFailure $ "Unknown test type " ++ show files
where
name =
"data/nix/tests/lang/" ++ the (map (takeFileName . dropExtensions) files)
"data/nix/tests/lang/" ++ the (fmap (takeFileName . dropExtensions) files)

fixup ("--arg" : x : y : rest) = "--arg" : (x ++ "=" ++ y) : fixup rest
fixup ("--argstr" : x : y : rest) = "--argstr" : (x ++ "=" ++ y) : fixup rest
Expand Down
2 changes: 1 addition & 1 deletion tests/ParserTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -122,7 +122,7 @@ case_inherit_selector = do
case_int_list = assertParseText "[1 2 3]" $ Fix $ NList
[ mkInt i | i <- [1,2,3] ]

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

case_mixed_list = do
assertParseText "[{a = 3;}.a (if true then null else false) null false 4 [] c.d or null]" $ Fix $ NList
Expand Down
8 changes: 4 additions & 4 deletions tests/PrettyParseTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -148,16 +148,16 @@ normalize = foldFix $ \case
NConstant (NFloat n) | n < 0 ->
Fix (NUnary NNeg (Fix (NConstant (NFloat (negate n)))))

NSet recur binds -> Fix (NSet recur (map normBinding binds))
NLet binds r -> Fix (NLet (map normBinding binds) r)
NSet recur binds -> Fix (NSet recur (fmap normBinding binds))
NLet binds r -> Fix (NLet (fmap normBinding binds) r)

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

r -> Fix r

where
normBinding (NamedVar path r pos) = NamedVar (NE.map normKey path) r pos
normBinding (Inherit mr names pos) = Inherit mr (map normKey names) pos
normBinding (Inherit mr names pos) = Inherit mr (fmap normKey names) pos

normKey (DynamicKey quoted) = DynamicKey (normAntiquotedString quoted)
normKey (StaticKey name ) = StaticKey name
Expand Down Expand Up @@ -220,7 +220,7 @@ prop_prettyparse p = do
normalise = unlines . fmap (reverse . dropWhile isSpace . reverse) . lines

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

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

0 comments on commit 3b8845f

Please sign in to comment.