fishy commit

This commit is contained in:
Joey Hess 2012-06-14 00:01:48 -04:00
parent 89dad12b35
commit e0095b0bdc
7 changed files with 9 additions and 9 deletions

View file

@ -242,7 +242,7 @@ cleanObjectLoc key = do
removeparents file n = do
let dir = parentDir file
maybe noop (const $ removeparents dir (n-1))
=<< catchMaybeIO (removeDirectory dir)
<=< catchMaybeIO $ removeDirectory dir
{- Removes a key's file from .git/annex/objects/ -}
removeAnnex :: Key -> Annex ()

View file

@ -23,13 +23,13 @@ import Config
addCommand :: String -> [CommandParam] -> [FilePath] -> Annex ()
addCommand command params files = do
q <- get
store =<< inRepo (Git.Queue.addCommand command params files q)
store <=< inRepo $ Git.Queue.addCommand command params files q
{- Adds an update-index stream to the queue. -}
addUpdateIndex :: Git.UpdateIndex.Streamer -> Annex ()
addUpdateIndex streamer = do
q <- get
store =<< inRepo (Git.Queue.addUpdateIndex streamer q)
store <=< inRepo $ Git.Queue.addUpdateIndex streamer q
{- Runs the queue if it is full. Should be called periodically. -}
flushWhenFull :: Annex ()

View file

@ -22,7 +22,7 @@ seek = [withNothing start]
start :: CommandStart
start = next $ next $ do
Annex.Branch.commit "update"
_ <- runhook =<< inRepo (Git.hookPath "annex-content")
_ <- runhook <=< inRepo $ Git.hookPath "annex-content"
return True
where
runhook (Just hook) = liftIO $ boolSystem hook []

View file

@ -84,7 +84,7 @@ checkRemoteUnused name = go =<< fromJust <$> Remote.byName (Just name)
_ <- check "" (remoteUnusedMsg r) (remoteunused r) 0
next $ return True
remoteunused r =
excludeReferenced =<< loggedKeysFor (Remote.uuid r)
excludeReferenced <=< loggedKeysFor $ Remote.uuid r
check :: FilePath -> ([(Int, Key)] -> String) -> Annex [Key] -> Int -> Annex Int
check file msg a c = do
@ -260,7 +260,7 @@ withKeysReferencedInGit a = do
withKeysReferencedInGitRef :: (Key -> Annex ()) -> Git.Ref -> Annex ()
withKeysReferencedInGitRef a ref = do
showAction $ "checking " ++ Git.Ref.describe ref
go =<< inRepo (LsTree.lsTree ref)
go <=< inRepo $ LsTree.lsTree ref
where
go [] = noop
go (l:ls)

View file

@ -100,7 +100,7 @@ rsyncUrls o k = map use annexHashes
f = keyFile k
store :: RsyncOpts -> Key -> Annex Bool
store o k = rsyncSend o k =<< inRepo (gitAnnexLocation k)
store o k = rsyncSend o k <=< inRepo $ gitAnnexLocation k
storeEncrypted :: RsyncOpts -> (Cipher, Key) -> Key -> Annex Bool
storeEncrypted o (cipher, enck) k = withTmp enck $ \tmp -> do

View file

@ -95,7 +95,7 @@ withValue v a params = do
-}
withField :: Option -> (Maybe String -> Annex a) -> (a -> CommandSeek) -> CommandSeek
withField option converter = withValue $
converter =<< Annex.getField (Option.name option)
converter <=< Annex.getField $ Option.name option
withFlag :: Option -> (Bool -> CommandSeek) -> CommandSeek
withFlag option = withValue $ Annex.getFlag (Option.name option)

View file

@ -84,7 +84,7 @@ inject source dest = do
logFiles :: FilePath -> Annex [FilePath]
logFiles dir = return . filter (".log" `isSuffixOf`)
=<< liftIO (getDirectoryContents dir)
<=< liftIO $ getDirectoryContents dir
push :: Annex ()
push = do