diff options
author | Joey Hess <joey@kitenet.net> | 2011-12-31 14:32:59 -0400 |
---|---|---|
committer | Joey Hess <joey@kitenet.net> | 2011-12-31 14:32:59 -0400 |
commit | 09905f66559f964ad36dc40da03d4f7f96804a91 (patch) | |
tree | b871c8a2372e6cba00aaa9b707c091f65837016b /Command | |
parent | 38195a6363e54874ce072eb2d3ced448e0b68e02 (diff) | |
parent | f0957426c586610d16ad9694e002b73324baa29a (diff) |
Merge branch 'autosync'
Diffstat (limited to 'Command')
-rw-r--r-- | Command/Copy.hs | 2 | ||||
-rw-r--r-- | Command/Drop.hs | 14 | ||||
-rw-r--r-- | Command/Find.hs | 2 | ||||
-rw-r--r-- | Command/Fix.hs | 2 | ||||
-rw-r--r-- | Command/Fsck.hs | 8 | ||||
-rw-r--r-- | Command/Get.hs | 2 | ||||
-rw-r--r-- | Command/InitRemote.hs | 4 | ||||
-rw-r--r-- | Command/Migrate.hs | 4 | ||||
-rw-r--r-- | Command/Move.hs | 12 | ||||
-rw-r--r-- | Command/Reinject.hs | 4 | ||||
-rw-r--r-- | Command/Sync.hs | 182 | ||||
-rw-r--r-- | Command/Unannex.hs | 2 | ||||
-rw-r--r-- | Command/Uninit.hs | 2 | ||||
-rw-r--r-- | Command/Unlock.hs | 2 | ||||
-rw-r--r-- | Command/Unused.hs | 6 | ||||
-rw-r--r-- | Command/Whereis.hs | 2 |
16 files changed, 174 insertions, 76 deletions
diff --git a/Command/Copy.hs b/Command/Copy.hs index 16de423ac..77beb4b4f 100644 --- a/Command/Copy.hs +++ b/Command/Copy.hs @@ -21,6 +21,6 @@ seek = [withNumCopies $ \n -> whenAnnexed $ start n] -- A copy is just a move that does not delete the source file. -- However, --auto mode avoids unnecessary copies. -start :: Maybe Int -> FilePath -> (Key, Backend Annex) -> CommandStart +start :: Maybe Int -> FilePath -> (Key, Backend) -> CommandStart start numcopies file (key, backend) = autoCopies key (<) numcopies $ Command.Move.start False file (key, backend) diff --git a/Command/Drop.hs b/Command/Drop.hs index 0a4c9dfd6..89e7c8e42 100644 --- a/Command/Drop.hs +++ b/Command/Drop.hs @@ -24,7 +24,7 @@ def = [dontCheck fromOpt $ command "drop" paramPaths seek seek :: [CommandSeek] seek = [withNumCopies $ \n -> whenAnnexed $ start n] -start :: Maybe Int -> FilePath -> (Key, Backend Annex) -> CommandStart +start :: Maybe Int -> FilePath -> (Key, Backend) -> CommandStart start numcopies file (key, _) = autoCopies key (>) numcopies $ do from <- Annex.getState Annex.fromremote case from of @@ -41,7 +41,7 @@ startLocal file numcopies key = stopUnless (inAnnex key) $ do showStart "drop" file next $ performLocal key numcopies -startRemote :: FilePath -> Maybe Int -> Key -> Remote.Remote Annex -> CommandStart +startRemote :: FilePath -> Maybe Int -> Key -> Remote -> CommandStart startRemote file numcopies key remote = do showStart "drop" file next $ performRemote key numcopies remote @@ -55,7 +55,7 @@ performLocal key numcopies = lockContent key $ do whenM (inAnnex key) $ removeAnnex key next $ cleanupLocal key -performRemote :: Key -> Maybe Int -> Remote.Remote Annex -> CommandPerform +performRemote :: Key -> Maybe Int -> Remote -> CommandPerform performRemote key numcopies remote = lockContent key $ do -- Filter the remote it's being dropped from out of the lists of -- places assumed to have the key, and places to check. @@ -79,7 +79,7 @@ cleanupLocal key = do logStatus key InfoMissing return True -cleanupRemote :: Key -> Remote.Remote Annex -> Bool -> CommandCleanup +cleanupRemote :: Key -> Remote -> Bool -> CommandCleanup cleanupRemote key remote ok = do -- better safe than sorry: assume the remote dropped the key -- even if it seemed to fail; the failure could have occurred @@ -90,7 +90,7 @@ cleanupRemote key remote ok = do {- Checks specified remotes to verify that enough copies of a key exist to - allow it to be safely removed (with no data loss). Can be provided with - some locations where the key is known/assumed to be present. -} -canDropKey :: Key -> Maybe Int -> [UUID] -> [Remote.Remote Annex] -> [UUID] -> Annex Bool +canDropKey :: Key -> Maybe Int -> [UUID] -> [Remote] -> [UUID] -> Annex Bool canDropKey key numcopiesM have check skip = do force <- Annex.getState Annex.force if force || numcopiesM == Just 0 @@ -99,7 +99,7 @@ canDropKey key numcopiesM have check skip = do need <- getNumCopies numcopiesM findCopies key need skip have check -findCopies :: Key -> Int -> [UUID] -> [UUID] -> [Remote.Remote Annex] -> Annex Bool +findCopies :: Key -> Int -> [UUID] -> [UUID] -> [Remote] -> Annex Bool findCopies key need skip = helper [] where helper bad have [] @@ -116,7 +116,7 @@ findCopies key need skip = helper [] (False, Left _) -> helper (r:bad) have rs _ -> helper bad have rs -notEnoughCopies :: Key -> Int -> [UUID] -> [UUID] -> [Remote.Remote Annex] -> Annex Bool +notEnoughCopies :: Key -> Int -> [UUID] -> [UUID] -> [Remote] -> Annex Bool notEnoughCopies key need have skip bad = do unsafe showLongNote $ diff --git a/Command/Find.hs b/Command/Find.hs index 1961e6b74..0c96369ee 100644 --- a/Command/Find.hs +++ b/Command/Find.hs @@ -24,7 +24,7 @@ def = [command "find" paramPaths seek "lists available files"] seek :: [CommandSeek] seek = [withFilesInGit $ whenAnnexed start] -start :: FilePath -> (Key, Backend Annex) -> CommandStart +start :: FilePath -> (Key, Backend) -> CommandStart start file (key, _) = do -- only files inAnnex are shown, unless the user has requested -- others via a limit diff --git a/Command/Fix.hs b/Command/Fix.hs index f264106c3..c4f981381 100644 --- a/Command/Fix.hs +++ b/Command/Fix.hs @@ -20,7 +20,7 @@ seek :: [CommandSeek] seek = [withFilesInGit $ whenAnnexed start] {- Fixes the symlink to an annexed file. -} -start :: FilePath -> (Key, Backend Annex) -> CommandStart +start :: FilePath -> (Key, Backend) -> CommandStart start file (key, _) = do link <- calcGitLink file key stopUnless ((/=) link <$> liftIO (readSymbolicLink file)) $ do diff --git a/Command/Fsck.hs b/Command/Fsck.hs index a803207e2..4e83455e1 100644 --- a/Command/Fsck.hs +++ b/Command/Fsck.hs @@ -30,12 +30,12 @@ seek = , withBarePresentKeys startBare ] -start :: Maybe Int -> FilePath -> (Key, Backend Annex) -> CommandStart +start :: Maybe Int -> FilePath -> (Key, Backend) -> CommandStart start numcopies file (key, backend) = do showStart "fsck" file next $ perform key file backend numcopies -perform :: Key -> FilePath -> Backend Annex -> Maybe Int -> CommandPerform +perform :: Key -> FilePath -> Backend -> Maybe Int -> CommandPerform perform key file backend numcopies = check -- order matters [ verifyLocationLog key file @@ -64,7 +64,7 @@ startBare key = case Backend.maybeLookupBackendName (Types.Key.keyBackendName ke {- Note that numcopies cannot be checked in a bare repository, because - getting the numcopies value requires a working copy with .gitattributes - files. -} -performBare :: Key -> Backend Annex -> CommandPerform +performBare :: Key -> Backend -> CommandPerform performBare key backend = check [ verifyLocationLog key (show key) , checkKeySize key @@ -136,7 +136,7 @@ checkKeySize key = do return False -checkBackend :: Backend Annex -> Key -> Annex Bool +checkBackend :: Backend -> Key -> Annex Bool checkBackend = Types.Backend.fsckKey checkKeyNumCopies :: Key -> FilePath -> Maybe Int -> Annex Bool diff --git a/Command/Get.hs b/Command/Get.hs index b7023e2de..f2b70baeb 100644 --- a/Command/Get.hs +++ b/Command/Get.hs @@ -21,7 +21,7 @@ def = [dontCheck fromOpt $ command "get" paramPaths seek seek :: [CommandSeek] seek = [withNumCopies $ \n -> whenAnnexed $ start n] -start :: Maybe Int -> FilePath -> (Key, Backend Annex) -> CommandStart +start :: Maybe Int -> FilePath -> (Key, Backend) -> CommandStart start numcopies file (key, _) = stopUnless (not <$> inAnnex key) $ autoCopies key (<) numcopies $ do from <- Annex.getState Annex.fromremote diff --git a/Command/InitRemote.hs b/Command/InitRemote.hs index 1e6bc2ef1..698d60455 100644 --- a/Command/InitRemote.hs +++ b/Command/InitRemote.hs @@ -42,7 +42,7 @@ start (name:ws) = do where config = Logs.Remote.keyValToConfig ws -perform :: R.RemoteType Annex -> UUID -> R.RemoteConfig -> CommandPerform +perform :: RemoteType -> UUID -> R.RemoteConfig -> CommandPerform perform t u c = do c' <- R.setup t u c next $ cleanup u c' @@ -77,7 +77,7 @@ remoteNames = do return $ mapMaybe (M.lookup nameKey . snd) $ M.toList m {- find the specified remote type -} -findType :: R.RemoteConfig -> Annex (R.RemoteType Annex) +findType :: R.RemoteConfig -> Annex RemoteType findType config = maybe unspecified specified $ M.lookup typeKey config where unspecified = error "Specify the type of remote with type=" diff --git a/Command/Migrate.hs b/Command/Migrate.hs index 8778743ff..f6467463d 100644 --- a/Command/Migrate.hs +++ b/Command/Migrate.hs @@ -21,7 +21,7 @@ def = [command "migrate" paramPaths seek "switch data to different backend"] seek :: [CommandSeek] seek = [withBackendFilesInGit $ \(b, f) -> whenAnnexed (start b) f] -start :: Maybe (Backend Annex) -> FilePath -> (Key, Backend Annex) -> CommandStart +start :: Maybe Backend -> FilePath -> (Key, Backend) -> CommandStart start b file (key, oldbackend) = do exists <- inAnnex key newbackend <- choosebackend b @@ -47,7 +47,7 @@ upgradableKey key = isNothing $ Types.Key.keySize key - backends that allow the filename to influence the keys they - generate. -} -perform :: FilePath -> Key -> Backend Annex -> CommandPerform +perform :: FilePath -> Key -> Backend -> CommandPerform perform file oldkey newbackend = do src <- inRepo $ gitAnnexLocation oldkey tmp <- fromRepo gitAnnexTmpDir diff --git a/Command/Move.hs b/Command/Move.hs index 85fdff739..bd1490b0c 100644 --- a/Command/Move.hs +++ b/Command/Move.hs @@ -23,7 +23,7 @@ def = [dontCheck toOpt $ dontCheck fromOpt $ seek :: [CommandSeek] seek = [withFilesInGit $ whenAnnexed $ start True] -start :: Bool -> FilePath -> (Key, Backend Annex) -> CommandStart +start :: Bool -> FilePath -> (Key, Backend) -> CommandStart start move file (key, _) = do noAuto to <- Annex.getState Annex.toremote @@ -54,7 +54,7 @@ showMoveAction False file = showStart "copy" file - A file's content can be moved even if there are insufficient copies to - allow it to be dropped. -} -toStart :: Remote.Remote Annex -> Bool -> FilePath -> Key -> CommandStart +toStart :: Remote -> Bool -> FilePath -> Key -> CommandStart toStart dest move file key = do u <- getUUID ishere <- inAnnex key @@ -63,7 +63,7 @@ toStart dest move file key = do else do showMoveAction move file next $ toPerform dest move key -toPerform :: Remote.Remote Annex -> Bool -> Key -> CommandPerform +toPerform :: Remote -> Bool -> Key -> CommandPerform toPerform dest move key = moveLock move key $ do -- Checking the remote is expensive, so not done in the start step. -- In fast mode, location tracking is assumed to be correct, @@ -105,7 +105,7 @@ toPerform dest move key = moveLock move key $ do - If the current repository already has the content, it is still removed - from the remote. -} -fromStart :: Remote.Remote Annex -> Bool -> FilePath -> Key -> CommandStart +fromStart :: Remote -> Bool -> FilePath -> Key -> CommandStart fromStart src move file key | move = go | otherwise = stopUnless (not <$> inAnnex key) go @@ -113,12 +113,12 @@ fromStart src move file key go = stopUnless (fromOk src key) $ do showMoveAction move file next $ fromPerform src move key -fromOk :: Remote.Remote Annex -> Key -> Annex Bool +fromOk :: Remote -> Key -> Annex Bool fromOk src key = do u <- getUUID remotes <- Remote.keyPossibilities key return $ u /= Remote.uuid src && any (== src) remotes -fromPerform :: Remote.Remote Annex -> Bool -> Key -> CommandPerform +fromPerform :: Remote -> Bool -> Key -> CommandPerform fromPerform src move key = moveLock move key $ do ishere <- inAnnex key if ishere diff --git a/Command/Reinject.hs b/Command/Reinject.hs index 0648e90fc..480806e11 100644 --- a/Command/Reinject.hs +++ b/Command/Reinject.hs @@ -33,7 +33,7 @@ start (src:dest:[]) next $ whenAnnexed (perform src) dest start _ = error "specify a src file and a dest file" -perform :: FilePath -> FilePath -> (Key, Backend Annex) -> CommandPerform +perform :: FilePath -> FilePath -> (Key, Backend) -> CommandPerform perform src _dest (key, backend) = do unlessM move $ error "mv failed!" next $ cleanup key backend @@ -45,7 +45,7 @@ perform src _dest (key, backend) = do move = getViaTmp key $ \tmp -> liftIO $ boolSystem "mv" [File src, File tmp] -cleanup :: Key -> Backend Annex -> CommandCleanup +cleanup :: Key -> Backend -> CommandCleanup cleanup key backend = do logStatus key InfoPresent diff --git a/Command/Sync.hs b/Command/Sync.hs index 36c4eeef0..445a37137 100644 --- a/Command/Sync.hs +++ b/Command/Sync.hs @@ -1,28 +1,74 @@ {- git-annex command - - Copyright 2011 Joey Hess <joey@kitenet.net> + - Copyright 2011 Joachim Breitner <mail@joachim-breitner.de> - - Licensed under the GNU GPL version 3 or higher. -} +{-# LANGUAGE BangPatterns #-} + module Command.Sync where import Common.Annex import Command +import qualified Remote +import qualified Annex import qualified Annex.Branch import qualified Git.Command -import qualified Git.Config +import qualified Git.Branch import qualified Git.Ref import qualified Git +import qualified Types.Remote +import qualified Remote.Git -import qualified Data.ByteString.Lazy.Char8 as L +import qualified Data.Map as M def :: [Command] -def = [command "sync" paramPaths seek "synchronize local repository with remote"] +def = [command "sync" (paramOptional (paramRepeating paramRemote)) + [seek] "synchronize local repository with remotes"] + +-- syncing involves several operations, any of which can independently fail +seek :: CommandSeek +seek rs = do + !branch <- fromMaybe nobranch <$> inRepo (Git.Branch.current) + remotes <- syncRemotes rs + return $ concat $ + [ [ commit ] + , [ mergeLocal branch ] + , [ pullRemote remote branch | remote <- remotes ] + , [ mergeAnnex ] + , [ pushLocal branch ] + , [ pushRemote remote branch | remote <- remotes ] + ] + where + nobranch = error "no branch is checked out" + +syncBranch :: Git.Ref -> Git.Ref +syncBranch = Git.Ref.under "refs/heads/synced/" + +remoteBranch :: Remote -> Git.Ref -> Git.Ref +remoteBranch remote = Git.Ref.under $ "refs/remotes/" ++ Remote.name remote --- syncing involves several operations, any of which can independantly fail -seek :: [CommandSeek] -seek = map withNothing [commit, pull, push] +syncRemotes :: [String] -> Annex [Remote] +syncRemotes rs = do + fast <- Annex.getState Annex.fast + if fast + then nub <$> pickfast + else wanted + where + pickfast = (++) <$> listed <*> (good =<< fastest <$> available) + wanted + | null rs = good =<< available + | otherwise = listed + listed = mapM Remote.byName rs + available = filter nonspecial <$> Remote.enabledRemoteList + good = filterM $ Remote.Git.repoAvail . Types.Remote.repo + nonspecial r = Types.Remote.remotetype r == Remote.Git.remote + fastest = fromMaybe [] . headMaybe . + map snd . sort . M.toList . costmap + costmap = M.fromListWith (++) . map costpair + costpair r = (Types.Remote.cost r, [r]) commit :: CommandStart commit = do @@ -31,44 +77,96 @@ commit = do showOutput -- Commit will fail when the tree is clean, so ignore failure. _ <- inRepo $ Git.Command.runBool "commit" - [Param "-a", Param "-m", Param "sync"] + [Param "-a", Param "-m", Param "git-annex automatic sync"] return True -pull :: CommandStart -pull = do - remote <- defaultRemote - showStart "pull" remote - next $ next $ do - showOutput - checkRemote remote - inRepo $ Git.Command.runBool "pull" [Param remote] +mergeLocal :: Git.Ref -> CommandStart +mergeLocal branch = go =<< needmerge + where + syncbranch = syncBranch branch + needmerge = do + unlessM (inRepo $ Git.Ref.exists syncbranch) $ + updateBranch syncbranch + inRepo $ Git.Branch.changed branch syncbranch + go False = stop + go True = do + showStart "merge" $ Git.Ref.describe syncbranch + next $ next $ mergeFrom syncbranch -push :: CommandStart -push = do - remote <- defaultRemote - showStart "push" remote - next $ next $ do - Annex.Branch.update +pushLocal :: Git.Ref -> CommandStart +pushLocal branch = do + updateBranch $ syncBranch branch + stop + +updateBranch :: Git.Ref -> Annex () +updateBranch syncbranch = + unlessM go $ error $ "failed to update " ++ show syncbranch + where + go = inRepo $ Git.Command.runBool "branch" + [ Param "-f" + , Param $ show $ Git.Ref.base syncbranch + ] + +pullRemote :: Remote -> Git.Ref -> CommandStart +pullRemote remote branch = do + showStart "pull" (Remote.name remote) + next $ do showOutput - inRepo $ Git.Command.runBool "push" [Param remote, matchingbranches] + fetched <- inRepo $ Git.Command.runBool "fetch" + [Param $ Remote.name remote] + if fetched + then next $ mergeRemote remote branch + else stop + +{- The remote probably has both a master and a synced/master branch. + - Which to merge from? Well, the master has whatever latest changes + - were committed, while the synced/master may have changes that some + - other remote synced to this remote. So, merge them both. -} +mergeRemote :: Remote -> Git.Ref -> CommandCleanup +mergeRemote remote branch = all id <$> (mapM merge =<< tomerge) + where + merge = mergeFrom . remoteBranch remote + tomerge = filterM (changed remote) [branch, syncBranch branch] + +pushRemote :: Remote -> Git.Ref -> CommandStart +pushRemote remote branch = go =<< needpush where - -- git push may be configured to not push matching - -- branches; this should ensure it always does. - matchingbranches = Param ":" - --- the remote defaults to origin when not configured -defaultRemote :: Annex String -defaultRemote = do - branch <- currentBranch - fromRepo $ Git.Config.get ("branch." ++ branch ++ ".remote") "origin" - -currentBranch :: Annex String -currentBranch = Git.Ref.describe . Git.Ref . firstLine . L.unpack <$> - inRepo (Git.Command.pipeRead [Param "symbolic-ref", Param "HEAD"]) - -checkRemote :: String -> Annex () -checkRemote remote = do - remoteurl <- fromRepo $ - Git.Config.get ("remote." ++ remote ++ ".url") "" - when (null remoteurl) $ do - error $ "No url is configured for the remote: " ++ remote + needpush = anyM (newer remote) [syncbranch, Annex.Branch.name] + go False = stop + go True = do + showStart "push" (Remote.name remote) + next $ next $ do + showOutput + inRepo $ Git.Command.runBool "push" $ + [ Param (Remote.name remote) + , Param (show $ Annex.Branch.name) + , Param refspec + ] + refspec = show (Git.Ref.base branch) ++ ":" ++ show (Git.Ref.base syncbranch) + syncbranch = syncBranch branch + +mergeAnnex :: CommandStart +mergeAnnex = do + Annex.Branch.forceUpdate + stop + +mergeFrom :: Git.Ref -> CommandCleanup +mergeFrom branch = do + showOutput + inRepo $ Git.Command.runBool "merge" [Param $ show branch] + +changed :: Remote -> Git.Ref -> Annex Bool +changed remote b = do + let r = remoteBranch remote b + e <- inRepo $ Git.Ref.exists r + if e + then inRepo $ Git.Branch.changed b r + else return False + +newer :: Remote -> Git.Ref -> Annex Bool +newer remote b = do + let r = remoteBranch remote b + e <- inRepo $ Git.Ref.exists r + if e + then inRepo $ Git.Branch.changed r b + else return True diff --git a/Command/Unannex.hs b/Command/Unannex.hs index 66611cbd7..fee67429d 100644 --- a/Command/Unannex.hs +++ b/Command/Unannex.hs @@ -22,7 +22,7 @@ def = [command "unannex" paramPaths seek "undo accidential add command"] seek :: [CommandSeek] seek = [withFilesInGit $ whenAnnexed start] -start :: FilePath -> (Key, Backend Annex) -> CommandStart +start :: FilePath -> (Key, Backend) -> CommandStart start file (key, _) = stopUnless (inAnnex key) $ do showStart "unannex" file next $ perform file key diff --git a/Command/Uninit.hs b/Command/Uninit.hs index 21ad4c7df..cef89a5cf 100644 --- a/Command/Uninit.hs +++ b/Command/Uninit.hs @@ -36,7 +36,7 @@ check = do seek :: [CommandSeek] seek = [withFilesInGit $ whenAnnexed startUnannex, withNothing start] -startUnannex :: FilePath -> (Key, Backend Annex) -> CommandStart +startUnannex :: FilePath -> (Key, Backend) -> CommandStart startUnannex file info = do -- Force fast mode before running unannex. This way, if multiple -- files link to a key, it will be left in the annex and hardlinked diff --git a/Command/Unlock.hs b/Command/Unlock.hs index 673a7038a..afee10145 100644 --- a/Command/Unlock.hs +++ b/Command/Unlock.hs @@ -26,7 +26,7 @@ seek = [withFilesInGit $ whenAnnexed start] {- The unlock subcommand replaces the symlink with a copy of the file's - content. -} -start :: FilePath -> (Key, Backend Annex) -> CommandStart +start :: FilePath -> (Key, Backend) -> CommandStart start file (key, _) = do showStart "unlock" file next $ perform file key diff --git a/Command/Unused.hs b/Command/Unused.hs index ef398b01e..8d45c51cb 100644 --- a/Command/Unused.hs +++ b/Command/Unused.hs @@ -66,7 +66,7 @@ checkRemoteUnused name = do checkRemoteUnused' =<< Remote.byName name next $ return True -checkRemoteUnused' :: Remote.Remote Annex -> Annex () +checkRemoteUnused' :: Remote -> Annex () checkRemoteUnused' r = do showAction "checking for unused data" remotehas <- loggedKeysFor (Remote.uuid r) @@ -112,14 +112,14 @@ unusedMsg' u header trailer = unlines $ ["(To see where data was previously used, try: git log --stat -S'KEY')"] ++ trailer -remoteUnusedMsg :: Remote.Remote Annex -> [(Int, Key)] -> String +remoteUnusedMsg :: Remote -> [(Int, Key)] -> String remoteUnusedMsg r u = unusedMsg' u ["Some annexed data on " ++ name ++ " is not used by any files:"] [dropMsg $ Just r] where name = Remote.name r -dropMsg :: Maybe (Remote.Remote Annex) -> String +dropMsg :: Maybe Remote -> String dropMsg Nothing = dropMsg' "" dropMsg (Just r) = dropMsg' $ " --from " ++ Remote.name r dropMsg' :: String -> String diff --git a/Command/Whereis.hs b/Command/Whereis.hs index eb2ae3d4e..9e57f361b 100644 --- a/Command/Whereis.hs +++ b/Command/Whereis.hs @@ -20,7 +20,7 @@ def = [command "whereis" paramPaths seek seek :: [CommandSeek] seek = [withFilesInGit $ whenAnnexed start] -start :: FilePath -> (Key, Backend Annex) -> CommandStart +start :: FilePath -> (Key, Backend) -> CommandStart start file (key, _) = do showStart "whereis" file next $ perform key |