Skip to content

Commit 701c2d9

Browse files
committed
for(M->)_; add traverse_, for_ into Utils
1 parent d2a7b28 commit 701c2d9

File tree

9 files changed

+27
-12
lines changed

9 files changed

+27
-12
lines changed

main/Main.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,6 @@ import Control.Monad
1717
import Control.Monad.Catch
1818
import Control.Monad.Free
1919
import Control.Monad.IO.Class
20-
import Data.Foldable ( traverse_ )
2120
import qualified Data.HashMap.Lazy as M
2221
import qualified Data.Map as Map
2322
import Data.List ( sortOn )
@@ -180,7 +179,7 @@ main = do
180179
)
181180
(\ v -> pure (k, pure (Free v)))
182181
nv
183-
forM_ xs $ \(k, mv) -> do
182+
for_ xs $ \(k, mv) -> do
184183
let path = prefix <> Text.unpack k
185184
(report, descend) = filterEntry path k
186185
when report $ do

main/Repl.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -102,7 +102,7 @@ main' iniVal = initState iniVal >>= \s -> flip evalStateT s
102102

103103
rcFile = do
104104
f <- liftIO $ Data.Text.IO.readFile ".hnixrc" `catch` handleMissing
105-
forM_ (fmap (words . Data.Text.unpack) $ Data.Text.lines f) $ \case
105+
for_ (words . Data.Text.unpack <$> Data.Text.lines f) $ \case
106106
((prefix:command) : xs) | prefix == commandPrefix -> do
107107
let arguments = unwords xs
108108
optMatcher command options arguments
@@ -269,7 +269,7 @@ browse :: (MonadNix e t f m, MonadIO m)
269269
-> Repl e t f m ()
270270
browse _ = do
271271
st <- get
272-
forM_ (Data.HashMap.Lazy.toList $ replCtx st) $ \(k, v) -> do
272+
for_ (Data.HashMap.Lazy.toList $ replCtx st) $ \(k, v) -> do
273273
liftIO $ putStr $ Data.Text.unpack $ k <> " = "
274274
printValue v
275275

@@ -298,7 +298,7 @@ typeof args = do
298298
Nothing -> do
299299
exec False line
300300

301-
forM_ mVal $ \val -> do
301+
for_ mVal $ \val -> do
302302
s <- lift . lift . showValueType $ val
303303
liftIO $ putStrLn s
304304

@@ -525,7 +525,7 @@ help :: (MonadNix e t f m, MonadIO m)
525525
-> Repl e t f m ()
526526
help hs _ = do
527527
liftIO $ putStrLn "Available commands:\n"
528-
forM_ hs $ \h ->
528+
for_ hs $ \h ->
529529
liftIO .
530530
Data.Text.IO.putStrLn .
531531
Prettyprinter.Render.Text.renderStrict .

src/Nix/Type/Assumption.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,7 @@ import Prelude hiding ( lookup )
1515

1616
import Nix.Type.Type
1717

18-
import Data.Foldable
18+
import Data.Foldable ( foldl' )
1919

2020
newtype Assumption = Assumption { assumptions :: [(Name, Type)] }
2121
deriving (Eq, Show)

src/Nix/Type/Env.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,7 @@ import Prelude hiding ( lookup )
1818

1919
import Nix.Type.Type
2020

21-
import Data.Foldable hiding ( toList )
21+
import Data.Foldable ( foldl' )
2222
import qualified Data.Map as Map
2323

2424
---------------------------------------------------------------------------------

src/Nix/Type/Infer.hs

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,10 @@ import Control.Monad.Ref
4141
import Control.Monad.ST
4242
import Control.Monad.State.Strict
4343
import Data.Fix ( foldFix )
44-
import Data.Foldable
44+
import Data.Foldable ( foldl'
45+
, foldrM
46+
, find
47+
)
4548
import qualified Data.HashMap.Lazy as M
4649
import Data.List ( delete
4750
, nub

src/Nix/Utils.hs

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -265,3 +265,15 @@ ifPure f =
265265
free
266266
f
267267
mempty
268+
269+
-- From @base@ @Data.Foldable@
270+
traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f ()
271+
traverse_ f = foldr c (pure ())
272+
-- See Note [List fusion and continuations in 'c']
273+
where c x k = f x *> k
274+
{-# inline c #-}
275+
276+
-- From @base@ @Data.Foldable@
277+
for_ :: (Foldable t, Applicative f) => t a -> (a -> f b) -> f ()
278+
for_ = flip traverse_
279+
{-# inline for_ #-}

src/Nix/Value/Equal.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -56,7 +56,7 @@ alignEqM eq fa fb = fmap (either (const False) (const True)) $ runExceptT $ do
5656
pairs <- forM (Data.Align.align fa fb) $ \case
5757
These a b -> pure (a, b)
5858
_ -> throwE ()
59-
forM_ pairs $ \(a, b) -> guard =<< lift (eq a b)
59+
for_ pairs $ \(a, b) -> guard =<< lift (eq a b)
6060

6161
alignEq :: (Align f, Traversable f) => (a -> b -> Bool) -> f a -> f b -> Bool
6262
alignEq eq fa fb = runIdentity $ alignEqM (\x y -> Identity (eq x y)) fa fb

tests/Main.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,7 @@ import Nix.Options
2323
import Nix.Parser
2424
import Nix.Standard
2525
import Nix.Value
26+
import Nix.Utils
2627
import qualified NixLanguageTests
2728
import qualified ParserTests
2829
import qualified PrettyTests
@@ -68,7 +69,7 @@ ensureNixpkgsCanParse =
6869
when (null files) $
6970
errorWithoutStackTrace $
7071
"Directory " <> show dir <> " does not have any files"
71-
forM_ files $ \file -> do
72+
for_ files $ \file -> do
7273
unless ("azure-cli/default.nix" `isSuffixOf` file ||
7374
"os-specific/linux/udisks/2-default.nix" `isSuffixOf` file) $ do
7475
-- Parse and deepseq the resulting expression tree, to ensure the

tests/ParserTests.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,7 @@ import Prettyprinter.Render.Text
2222
import Test.Tasty
2323
import Test.Tasty.HUnit
2424
import Test.Tasty.TH
25-
import Data.Foldable (traverse_)
25+
import Nix.Utils
2626

2727
case_constant_int = assertParseText "234" $ mkInt 234
2828

0 commit comments

Comments
 (0)