use forM_ in a few places

This commit is contained in:
Joey Hess 2011-01-31 23:27:53 -04:00
parent 27056daccd
commit 755029ae0e
3 changed files with 6 additions and 6 deletions

View file

@ -7,7 +7,7 @@
module Command.Unused where module Command.Unused where
import Control.Monad (filterM, unless) import Control.Monad (filterM, unless, forM_)
import Control.Monad.State (liftIO) import Control.Monad.State (liftIO)
import qualified Data.Set as S import qualified Data.Set as S
import Data.Maybe import Data.Maybe
@ -88,7 +88,7 @@ unusedKeys = do
-- Tmp files that are dups of content already present can simply -- Tmp files that are dups of content already present can simply
-- be removed. -- be removed.
liftIO $ mapM_ (\t -> removeFile $ gitAnnexTmpLocation g t) duptmp liftIO $ forM_ duptmp $ \t -> removeFile $ gitAnnexTmpLocation g t
return (unused, staletmp) return (unused, staletmp)

View file

@ -16,7 +16,7 @@ import qualified Data.Map as M
import System.IO import System.IO
import System.Cmd.Utils import System.Cmd.Utils
import Data.String.Utils import Data.String.Utils
import Control.Monad (unless) import Control.Monad (unless, forM_)
import qualified GitRepo as Git import qualified GitRepo as Git
@ -45,7 +45,7 @@ add queue subcommand params file = M.insertWith (++) action [file] queue
{- Runs a queue on a git repository. -} {- Runs a queue on a git repository. -}
run :: Git.Repo -> Queue -> IO () run :: Git.Repo -> Queue -> IO ()
run repo queue = do run repo queue = do
mapM_ (uncurry $ runAction repo) $ M.toList queue forM_ (M.toList queue) $ uncurry $ runAction repo
return () return ()
{- Runs an Action on a list of files in a git repository. {- Runs an Action on a list of files in a git repository.

View file

@ -10,7 +10,7 @@ module Upgrade where
import System.IO.Error (try) import System.IO.Error (try)
import System.Directory import System.Directory
import Control.Monad.State (liftIO) import Control.Monad.State (liftIO)
import Control.Monad (filterM) import Control.Monad (filterM, forM_)
import System.Posix.Files import System.Posix.Files
import System.FilePath import System.FilePath
@ -41,7 +41,7 @@ upgradeFrom0 = do
-- do the reorganisation of the files -- do the reorganisation of the files
let olddir = gitAnnexDir g let olddir = gitAnnexDir g
keys <- getKeysPresent0' olddir keys <- getKeysPresent0' olddir
mapM_ (\k -> moveAnnex k $ olddir </> keyFile k) keys forM_ keys $ \k -> moveAnnex k $ olddir </> keyFile k
-- update the symlinks to the files -- update the symlinks to the files
files <- liftIO $ Git.inRepo g [Git.workTree g] files <- liftIO $ Git.inRepo g [Git.workTree g]