diff --git a/Annex.hs b/Annex.hs index 2148dd6252..06d642b742 100644 --- a/Annex.hs +++ b/Annex.hs @@ -20,10 +20,12 @@ import Control.Monad.State (liftIO, StateT, runStateT, evalStateT, liftM, get, put) import qualified GitRepo as Git -import qualified GitQueue -import qualified BackendClass -import qualified RemoteClass -import qualified CryptoTypes +import GitQueue +import Types.Backend +import Types.Remote +import Types.Crypto +import TrustLevel +import Types.UUID -- git-annex's monad type Annex = StateT AnnexState IO @@ -31,41 +33,45 @@ type Annex = StateT AnnexState IO -- internal state storage data AnnexState = AnnexState { repo :: Git.Repo - , backends :: [BackendClass.Backend Annex] - , supportedBackends :: [BackendClass.Backend Annex] - , remotes :: [RemoteClass.Remote Annex] - , repoqueue :: GitQueue.Queue + , backends :: [Backend Annex] + , supportedBackends :: [Backend Annex] + , remotes :: [Remote Annex] + , repoqueue :: Queue , quiet :: Bool , force :: Bool , fast :: Bool , forcebackend :: Maybe String + , forcenumcopies :: Maybe Int , defaultkey :: Maybe String , toremote :: Maybe String , fromremote :: Maybe String , exclude :: [String] - , cipher :: Maybe CryptoTypes.Cipher + , forcetrust :: [(UUID, TrustLevel)] + , cipher :: Maybe Cipher } -newState :: Git.Repo -> [BackendClass.Backend Annex] -> AnnexState +newState :: Git.Repo -> [Backend Annex] -> AnnexState newState gitrepo allbackends = AnnexState { repo = gitrepo , backends = [] , remotes = [] , supportedBackends = allbackends - , repoqueue = GitQueue.empty + , repoqueue = empty , quiet = False , force = False , fast = False , forcebackend = Nothing + , forcenumcopies = Nothing , defaultkey = Nothing , toremote = Nothing , fromremote = Nothing , exclude = [] + , forcetrust = [] , cipher = Nothing } {- Create and returns an Annex state object for the specified git repo. -} -new :: Git.Repo -> [BackendClass.Backend Annex] -> IO AnnexState +new :: Git.Repo -> [Backend Annex] -> IO AnnexState new gitrepo allbackends = do gitrepo' <- liftIO $ Git.configRead gitrepo return $ newState gitrepo' allbackends diff --git a/Backend.hs b/Backend.hs index 645bfdfc3f..78a53d02c7 100644 --- a/Backend.hs +++ b/Backend.hs @@ -42,8 +42,8 @@ import Locations import qualified GitRepo as Git import qualified Annex import Types -import Key -import qualified BackendClass as B +import Types.Key +import qualified Types.Backend as B import Messages import Content import DataUnits diff --git a/Backend/File.hs b/Backend/File.hs index b86413e400..386af02663 100644 --- a/Backend/File.hs +++ b/Backend/File.hs @@ -18,7 +18,7 @@ import Control.Monad.State (liftIO) import Data.List import Data.String.Utils -import BackendClass +import Types.Backend import LocationLog import qualified Remote import qualified GitRepo as Git @@ -28,7 +28,7 @@ import Types import UUID import Messages import Trust -import Key +import Types.Key backend :: Backend Annex backend = Backend { @@ -81,7 +81,7 @@ copyKeyFile key file = do Left _ -> return False else return True docopy r continue = do - showNote $ "copying from " ++ Remote.name r ++ "..." + showNote $ "from " ++ Remote.name r ++ "..." copied <- Remote.retrieveKeyFile r key file if copied then return True @@ -152,12 +152,16 @@ showTriedRemotes remotes = showLongNote $ "Unable to access these remotes: " ++ (join ", " $ map Remote.name remotes) +{- If a value is specified, it is used; otherwise the default is looked up + - in git config. forcenumcopies overrides everything. -} getNumCopies :: Maybe Int -> Annex Int -getNumCopies (Just n) = return n -getNumCopies Nothing = do - g <- Annex.gitRepo - return $ read $ Git.configGet g config "1" +getNumCopies v = + Annex.getState Annex.forcenumcopies >>= maybe (use v) (return . id) where + use (Just n) = return n + use Nothing = do + g <- Annex.gitRepo + return $ read $ Git.configGet g config "1" config = "annex.numcopies" {- Ideally, all keys have file size metadata. Old keys may not. -} diff --git a/Backend/SHA.hs b/Backend/SHA.hs index 6d721038c3..8ed00b7073 100644 --- a/Backend/SHA.hs +++ b/Backend/SHA.hs @@ -17,15 +17,15 @@ import System.Posix.Files import System.FilePath import qualified Backend.File -import BackendClass import Messages import qualified Annex import Locations import Content import Types +import Types.Backend +import Types.Key import Utility import qualified SysConfig -import Key type SHASize = Int @@ -119,7 +119,7 @@ checkKeyChecksum size key = do then return True else do s <- shaN size file - if s == keyName key + if s == dropExtension (keyName key) then return True else do dest <- moveBad key diff --git a/Backend/URL.hs b/Backend/URL.hs index 3068c30270..e41004dd46 100644 --- a/Backend/URL.hs +++ b/Backend/URL.hs @@ -10,10 +10,10 @@ module Backend.URL (backends) where import Control.Monad.State (liftIO) import Types -import BackendClass +import Types.Backend import Utility import Messages -import Key +import Types.Key backends :: [Backend Annex] backends = [backend] diff --git a/Backend/WORM.hs b/Backend/WORM.hs index b33c607632..dc2e48adce 100644 --- a/Backend/WORM.hs +++ b/Backend/WORM.hs @@ -12,9 +12,9 @@ import System.FilePath import System.Posix.Files import qualified Backend.File -import BackendClass +import Types.Backend import Types -import Key +import Types.Key backends :: [Backend Annex] backends = [backend] diff --git a/CmdLine.hs b/CmdLine.hs index 684ebf979a..861a31be97 100644 --- a/CmdLine.hs +++ b/CmdLine.hs @@ -28,8 +28,8 @@ import Messages import UUID {- Runs the passed command line. -} -dispatch :: Git.Repo -> [String] -> [Command] -> [Option] -> String -> IO () -dispatch gitrepo args cmds options header = do +dispatch :: [String] -> [Command] -> [Option] -> String -> Git.Repo -> IO () +dispatch args cmds options header gitrepo = do setupConsole state <- Annex.new gitrepo allBackends (actions, state') <- Annex.run state $ parseCmd args header cmds options diff --git a/Command.hs b/Command.hs index 0da847d24d..228c1f40e9 100644 --- a/Command.hs +++ b/Command.hs @@ -24,7 +24,7 @@ import qualified Annex import qualified GitRepo as Git import Locations import Utility -import Key +import Types.Key {- A command runs in four stages. - diff --git a/Command/DropUnused.hs b/Command/DropUnused.hs index 1bb3b7f970..0f99814471 100644 --- a/Command/DropUnused.hs +++ b/Command/DropUnused.hs @@ -22,7 +22,7 @@ import qualified Command.Move import qualified Remote import qualified GitRepo as Git import Backend -import Key +import Types.Key import Utility type UnusedMap = M.Map String Key diff --git a/Command/FromKey.hs b/Command/FromKey.hs index ca61094eb4..34816d6574 100644 --- a/Command/FromKey.hs +++ b/Command/FromKey.hs @@ -18,7 +18,7 @@ import Utility import qualified Backend import Content import Messages -import Key +import Types.Key command :: [Command] command = [repoCommand "fromkey" paramPath seek diff --git a/Command/Get.hs b/Command/Get.hs index 90c0540960..50dc009feb 100644 --- a/Command/Get.hs +++ b/Command/Get.hs @@ -9,9 +9,12 @@ module Command.Get where import Command import qualified Backend +import qualified Annex +import qualified Remote import Types import Content import Messages +import qualified Command.Move command :: [Command] command = [repoCommand "get" paramPath seek @@ -20,7 +23,6 @@ command = [repoCommand "get" paramPath seek seek :: [CommandSeek] seek = [withFilesInGit start] -{- Gets an annexed file from one of the backends. -} start :: CommandStartString start file = isAnnexed file $ \(key, backend) -> do inannex <- inAnnex key @@ -28,7 +30,12 @@ start file = isAnnexed file $ \(key, backend) -> do then stop else do showStart "get" file - next $ perform key backend + from <- Annex.getState Annex.fromremote + case from of + Nothing -> next $ perform key backend + Just name -> do + src <- Remote.byName name + next $ Command.Move.fromPerform src False key perform :: Key -> Backend Annex -> CommandPerform perform key backend = do diff --git a/Command/InitRemote.hs b/Command/InitRemote.hs index 460f14de2c..41d3c37c71 100644 --- a/Command/InitRemote.hs +++ b/Command/InitRemote.hs @@ -16,7 +16,7 @@ import Data.String.Utils import Command import qualified Annex import qualified Remote -import qualified RemoteClass +import qualified Types.Remote as R import qualified GitRepo as Git import Utility import Types @@ -54,12 +54,12 @@ start ws = notBareRepo $ do else err $ "Either a new name, or one of these existing special remotes: " ++ join " " names -perform :: RemoteClass.RemoteType Annex -> UUID -> RemoteClass.RemoteConfig -> CommandPerform +perform :: R.RemoteType Annex -> UUID -> R.RemoteConfig -> CommandPerform perform t u c = do - c' <- RemoteClass.setup t u c + c' <- R.setup t u c next $ cleanup u c' -cleanup :: UUID -> RemoteClass.RemoteConfig -> CommandCleanup +cleanup :: UUID -> R.RemoteConfig -> CommandCleanup cleanup u c = do Remote.configSet u c g <- Annex.gitRepo @@ -73,7 +73,7 @@ cleanup u c = do return True {- Look up existing remote's UUID and config by name, or generate a new one -} -findByName :: String -> Annex (UUID, RemoteClass.RemoteConfig) +findByName :: String -> Annex (UUID, R.RemoteConfig) findByName name = do m <- Remote.readRemoteLog maybe generate return $ findByName' name m @@ -82,7 +82,7 @@ findByName name = do uuid <- liftIO $ genUUID return (uuid, M.insert nameKey name M.empty) -findByName' :: String -> M.Map UUID RemoteClass.RemoteConfig -> Maybe (UUID, RemoteClass.RemoteConfig) +findByName' :: String -> M.Map UUID R.RemoteConfig -> Maybe (UUID, R.RemoteConfig) findByName' n m = if null matches then Nothing else Just $ head matches where matches = filter (matching . snd) $ M.toList m @@ -98,14 +98,14 @@ remoteNames = do return $ catMaybes $ map ((M.lookup nameKey) . snd) $ M.toList m {- find the specified remote type -} -findType :: RemoteClass.RemoteConfig -> Annex (RemoteClass.RemoteType Annex) +findType :: R.RemoteConfig -> Annex (R.RemoteType Annex) findType config = maybe unspecified specified $ M.lookup typeKey config where unspecified = error "Specify the type of remote with type=" specified s = case filter (findtype s) Remote.remoteTypes of [] -> error $ "Unknown remote type " ++ s (t:_) -> return t - findtype s i = RemoteClass.typename i == s + findtype s i = R.typename i == s {- The name of a configured remote is stored in its config using this key. -} nameKey :: String diff --git a/Command/Status.hs b/Command/Status.hs index dd518416cf..1a7f694ba8 100644 --- a/Command/Status.hs +++ b/Command/Status.hs @@ -14,8 +14,8 @@ import Data.List import qualified Data.Map as M import qualified Annex -import qualified BackendClass -import qualified RemoteClass +import qualified Types.Backend as B +import qualified Types.Remote as R import qualified Remote import qualified Command.Unused import qualified GitRepo as Git @@ -23,7 +23,7 @@ import Command import Types import DataUnits import Content -import Key +import Types.Key import Locations -- a named computation that produces a statistic @@ -97,11 +97,11 @@ showStat s = calc =<< s supported_backends :: Stat supported_backends = stat "supported backends" $ lift (Annex.getState Annex.supportedBackends) >>= - return . unwords . (map BackendClass.name) + return . unwords . (map B.name) supported_remote_types :: Stat supported_remote_types = stat "supported remote types" $ - return $ unwords $ map RemoteClass.typename Remote.remoteTypes + return $ unwords $ map R.typename Remote.remoteTypes local_annex_size :: Stat local_annex_size = stat "local annex size" $ diff --git a/Content.hs b/Content.hs index ec7a3776bf..57977ce344 100644 --- a/Content.hs +++ b/Content.hs @@ -41,7 +41,7 @@ import qualified Annex import qualified AnnexQueue import Utility import StatFS -import Key +import Types.Key import DataUnits import Config diff --git a/Crypto.hs b/Crypto.hs index 42f1389507..e84e397f2e 100644 --- a/Crypto.hs +++ b/Crypto.hs @@ -43,11 +43,11 @@ import System.Exit import System.Environment import Types -import Key -import RemoteClass +import Types.Key +import Types.Remote import Utility import Base64 -import CryptoTypes +import Types.Crypto {- The first half of a Cipher is used for HMAC; the remainder - is used as the GPG symmetric encryption passphrase. diff --git a/GitAnnex.hs b/GitAnnex.hs index 99aec187a9..103ee262f2 100644 --- a/GitAnnex.hs +++ b/GitAnnex.hs @@ -13,7 +13,10 @@ import qualified GitRepo as Git import CmdLine import Command import Options +import Utility +import TrustLevel import qualified Annex +import qualified Remote import qualified Command.Add import qualified Command.Unannex @@ -90,17 +93,24 @@ options = commonOptions ++ "specify from where to transfer content" , Option ['x'] ["exclude"] (ReqArg addexclude paramGlob) "skip files matching the glob pattern" + , Option ['N'] ["numcopies"] (ReqArg setnumcopies paramNumber) + "override default number of copies" + , Option [] ["trust"] (ReqArg (Remote.forceTrust Trusted) paramRemote) + "override trust setting" + , Option [] ["semitrust"] (ReqArg (Remote.forceTrust SemiTrusted) paramRemote) + "override trust setting back to default value" + , Option [] ["untrust"] (ReqArg (Remote.forceTrust UnTrusted) paramRemote) + "override trust setting to untrusted" ] where - setkey v = Annex.changeState $ \s -> s { Annex.defaultkey = Just v } setto v = Annex.changeState $ \s -> s { Annex.toremote = Just v } setfrom v = Annex.changeState $ \s -> s { Annex.fromremote = Just v } - addexclude v = Annex.changeState $ \s -> s { Annex.exclude = v:(Annex.exclude s) } + addexclude v = Annex.changeState $ \s -> s { Annex.exclude = v:Annex.exclude s } + setnumcopies v = Annex.changeState $ \s -> s {Annex.forcenumcopies = readMaybe v } + setkey v = Annex.changeState $ \s -> s { Annex.defaultkey = Just v } header :: String header = "Usage: git-annex command [option ..]" run :: [String] -> IO () -run args = do - gitrepo <- Git.repoFromCwd - dispatch gitrepo args cmds options header +run args = dispatch args cmds options header =<< Git.repoFromCwd diff --git a/Locations.hs b/Locations.hs index 38a320a2b2..da781ac83a 100644 --- a/Locations.hs +++ b/Locations.hs @@ -36,7 +36,7 @@ import Word import Data.Hash.MD5 import Types -import Key +import Types.Key import qualified GitRepo as Git {- Conventions: diff --git a/Remote.hs b/Remote.hs index 7df84a5da6..2e956cb81c 100644 --- a/Remote.hs +++ b/Remote.hs @@ -14,11 +14,13 @@ module Remote ( removeKey, hasKey, hasKeyCheap, + keyPossibilities, + forceTrust, remoteTypes, + genList, byName, nameToUUID, - keyPossibilities, remotesWithUUID, remotesWithoutUUID, @@ -38,15 +40,15 @@ import qualified Data.Map as M import Data.Maybe import Data.Char -import RemoteClass import Types +import Types.Remote import UUID import qualified Annex -import Trust -import LocationLog import Locations import Utility import Config +import Trust +import LocationLog import qualified Remote.Git import qualified Remote.S3 @@ -104,6 +106,14 @@ nameToUUID :: String -> Annex UUID nameToUUID "." = getUUID =<< Annex.gitRepo -- special case for current repo nameToUUID n = liftM uuid (byName n) +{- Filters a list of remotes to ones that have the listed uuids. -} +remotesWithUUID :: [Remote Annex] -> [UUID] -> [Remote Annex] +remotesWithUUID rs us = filter (\r -> uuid r `elem` us) rs + +{- Filters a list of remotes to ones that do not have the listed uuids. -} +remotesWithoutUUID :: [Remote Annex] -> [UUID] -> [Remote Annex] +remotesWithoutUUID rs us = filter (\r -> uuid r `notElem` us) rs + {- Cost ordered lists of remotes that the LocationLog indicate may have a key. - - Also returns a list of UUIDs that are trusted to have the key @@ -128,13 +138,11 @@ keyPossibilities key = do return (sort validremotes, validtrusteduuids) -{- Filters a list of remotes to ones that have the listed uuids. -} -remotesWithUUID :: [Remote Annex] -> [UUID] -> [Remote Annex] -remotesWithUUID rs us = filter (\r -> uuid r `elem` us) rs - -{- Filters a list of remotes to ones that do not have the listed uuids. -} -remotesWithoutUUID :: [Remote Annex] -> [UUID] -> [Remote Annex] -remotesWithoutUUID rs us = filter (\r -> uuid r `notElem` us) rs +forceTrust :: TrustLevel -> String -> Annex () +forceTrust level remotename = do + r <- Remote.nameToUUID remotename + Annex.changeState $ \s -> + s { Annex.forcetrust = (r, level):Annex.forcetrust s } {- Filename of remote.log. -} remoteLog :: Annex FilePath diff --git a/Remote/Bup.hs b/Remote/Bup.hs index c40826e5eb..c011c979ca 100644 --- a/Remote/Bup.hs +++ b/Remote/Bup.hs @@ -19,8 +19,8 @@ import System.FilePath import Data.List.Utils import System.Cmd.Utils -import RemoteClass import Types +import Types.Remote import qualified GitRepo as Git import qualified Annex import UUID diff --git a/Remote/Directory.hs b/Remote/Directory.hs index dedab473f3..7b5917dca8 100644 --- a/Remote/Directory.hs +++ b/Remote/Directory.hs @@ -16,8 +16,8 @@ import Control.Monad.State (liftIO) import System.Directory hiding (copyFile) import System.FilePath -import RemoteClass import Types +import Types.Remote import qualified GitRepo as Git import qualified Annex import UUID diff --git a/Remote/Encryptable.hs b/Remote/Encryptable.hs index 68ecfd01e6..443f5cf83d 100644 --- a/Remote/Encryptable.hs +++ b/Remote/Encryptable.hs @@ -11,7 +11,7 @@ import qualified Data.Map as M import Control.Monad.State (liftIO) import Types -import RemoteClass +import Types.Remote import Crypto import qualified Annex import Messages diff --git a/Remote/Git.hs b/Remote/Git.hs index e6df6be46e..67d49df7d2 100644 --- a/Remote/Git.hs +++ b/Remote/Git.hs @@ -12,8 +12,8 @@ import Control.Monad.State (liftIO) import qualified Data.Map as M import System.Cmd.Utils -import RemoteClass import Types +import Types.Remote import qualified GitRepo as Git import qualified Annex import qualified AnnexQueue diff --git a/Remote/Hook.hs b/Remote/Hook.hs index dc4d392741..cc511965f8 100644 --- a/Remote/Hook.hs +++ b/Remote/Hook.hs @@ -18,8 +18,8 @@ import System.IO import System.IO.Error (try) import System.Exit -import RemoteClass import Types +import Types.Remote import qualified GitRepo as Git import qualified Annex import UUID diff --git a/Remote/Rsync.hs b/Remote/Rsync.hs index 9d32ad19b9..bf1bbd8707 100644 --- a/Remote/Rsync.hs +++ b/Remote/Rsync.hs @@ -16,8 +16,8 @@ import System.Directory import System.Posix.Files import System.Posix.Process -import RemoteClass import Types +import Types.Remote import qualified GitRepo as Git import qualified Annex import UUID diff --git a/Remote/S3real.hs b/Remote/S3real.hs index baf570593e..2479dfa023 100644 --- a/Remote/S3real.hs +++ b/Remote/S3real.hs @@ -24,8 +24,9 @@ import System.Environment import System.Posix.Files import System.Posix.Env (setEnv) -import RemoteClass import Types +import Types.Remote +import Types.Key import qualified GitRepo as Git import qualified Annex import UUID @@ -35,7 +36,6 @@ import Config import Remote.Special import Remote.Encryptable import Crypto -import Key import Content import Base64 diff --git a/Remote/Special.hs b/Remote/Special.hs index 53ac2c6eed..7d2ea1d704 100644 --- a/Remote/Special.hs +++ b/Remote/Special.hs @@ -13,7 +13,7 @@ import Data.String.Utils import Control.Monad.State (liftIO) import Types -import RemoteClass +import Types.Remote import qualified GitRepo as Git import qualified Annex import UUID diff --git a/Trust.hs b/Trust.hs index 7b2cf9ff88..aaca3b3706 100644 --- a/Trust.hs +++ b/Trust.hs @@ -1,4 +1,4 @@ -{- git-annex trust levels +{- git-annex trust - - Copyright 2010 Joey Hess - @@ -17,6 +17,7 @@ module Trust ( import Control.Monad.State import qualified Data.Map as M +import TrustLevel import qualified GitRepo as Git import Types import UUID @@ -24,19 +25,6 @@ import Locations import qualified Annex import Utility -data TrustLevel = SemiTrusted | UnTrusted | Trusted - deriving Eq - -instance Show TrustLevel where - show SemiTrusted = "?" - show UnTrusted = "0" - show Trusted = "1" - -instance Read TrustLevel where - readsPrec _ "1" = [(Trusted, "")] - readsPrec _ "0" = [(UnTrusted, "")] - readsPrec _ _ = [(SemiTrusted, "")] - {- Filename of trust.log. -} trustLog :: Annex FilePath trustLog = do @@ -49,18 +37,20 @@ trustGet level = do m <- trustMap return $ M.keys $ M.filter (== level) m -{- Read the trustLog into a map. -} +{- Read the trustLog into a map, overriding with any + - values from forcetrust -} trustMap :: Annex (M.Map UUID TrustLevel) trustMap = do logfile <- trustLog + overrides <- Annex.getState Annex.forcetrust s <- liftIO $ catch (readFile logfile) ignoreerror - return $ trustMapParse s + return $ M.fromList $ trustMapParse s ++ overrides where ignoreerror _ = return "" {- Trust map parser. -} -trustMapParse :: String -> M.Map UUID TrustLevel -trustMapParse s = M.fromList $ map pair $ filter (not . null) $ lines s +trustMapParse :: String -> [(UUID, TrustLevel)] +trustMapParse s = map pair $ filter (not . null) $ lines s where pair l | length w > 1 = (w !! 0, read (w !! 1) :: TrustLevel) diff --git a/TrustLevel.hs b/TrustLevel.hs new file mode 100644 index 0000000000..5da142ca30 --- /dev/null +++ b/TrustLevel.hs @@ -0,0 +1,23 @@ +{- git-annex trust levels + - + - Copyright 2010 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. + -} + +module TrustLevel ( + TrustLevel(..), +) where + +data TrustLevel = SemiTrusted | UnTrusted | Trusted + deriving Eq + +instance Show TrustLevel where + show SemiTrusted = "?" + show UnTrusted = "0" + show Trusted = "1" + +instance Read TrustLevel where + readsPrec _ "1" = [(Trusted, "")] + readsPrec _ "0" = [(UnTrusted, "")] + readsPrec _ _ = [(SemiTrusted, "")] diff --git a/Types.hs b/Types.hs index 503e27d312..6353f6da68 100644 --- a/Types.hs +++ b/Types.hs @@ -11,6 +11,6 @@ module Types ( Key ) where -import BackendClass import Annex -import Key +import Types.Backend +import Types.Key diff --git a/BackendClass.hs b/Types/Backend.hs similarity index 96% rename from BackendClass.hs rename to Types/Backend.hs index b2d8879c2f..8100eaf285 100644 --- a/BackendClass.hs +++ b/Types/Backend.hs @@ -7,9 +7,9 @@ - Licensed under the GNU GPL version 3 or higher. -} -module BackendClass where +module Types.Backend where -import Key +import Types.Key data Backend a = Backend { -- name of this backend diff --git a/CryptoTypes.hs b/Types/Crypto.hs similarity index 94% rename from CryptoTypes.hs rename to Types/Crypto.hs index ba22c4cbe8..a39a016b8b 100644 --- a/CryptoTypes.hs +++ b/Types/Crypto.hs @@ -5,7 +5,7 @@ - Licensed under the GNU GPL version 3 or higher. -} -module CryptoTypes where +module Types.Crypto where import Data.String.Utils diff --git a/Key.hs b/Types/Key.hs similarity index 95% rename from Key.hs rename to Types/Key.hs index e1d8ee34d0..1d9bf8e11c 100644 --- a/Key.hs +++ b/Types/Key.hs @@ -1,11 +1,13 @@ {- git-annex Key data type + - + - Most things should not need this, using Types instead - - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} -module Key ( +module Types.Key ( Key(..), stubKey, readKey, diff --git a/RemoteClass.hs b/Types/Remote.hs similarity index 96% rename from RemoteClass.hs rename to Types/Remote.hs index f954e4ff8f..01ced04ae1 100644 --- a/RemoteClass.hs +++ b/Types/Remote.hs @@ -1,4 +1,4 @@ -{- git-annex remotes class +{- git-annex remotes types - - Most things should not need this, using Remote instead - @@ -7,13 +7,13 @@ - Licensed under the GNU GPL version 3 or higher. -} -module RemoteClass where +module Types.Remote where import Control.Exception import Data.Map as M import qualified GitRepo as Git -import Key +import Types.Key type RemoteConfig = M.Map String String diff --git a/Types/UUID.hs b/Types/UUID.hs new file mode 100644 index 0000000000..eb3497fa94 --- /dev/null +++ b/Types/UUID.hs @@ -0,0 +1,11 @@ +{- git-annex UUID type + - + - Copyright 2011 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. + -} + +module Types.UUID where + +-- might be nice to have a newtype, but lots of stuff treats uuids as strings +type UUID = String diff --git a/UUID.hs b/UUID.hs index 0d7aee1414..f222f7a9d4 100644 --- a/UUID.hs +++ b/UUID.hs @@ -31,14 +31,13 @@ import Data.Maybe import qualified GitRepo as Git import Types +import Types.UUID import Locations import qualified Annex import Utility import qualified SysConfig import Config -type UUID = String - configkey :: String configkey = "annex.uuid" diff --git a/Upgrade/V1.hs b/Upgrade/V1.hs index 9278bce603..1e634e00e8 100644 --- a/Upgrade/V1.hs +++ b/Upgrade/V1.hs @@ -18,7 +18,7 @@ import System.Posix.Types import Data.Maybe import Data.Char -import Key +import Types.Key import Content import Types import Locations diff --git a/debian/changelog b/debian/changelog index c626191634..3e13ce0d04 100644 --- a/debian/changelog +++ b/debian/changelog @@ -1,3 +1,12 @@ +git-annex (0.20110610) unstable; urgency=low + + * Add --numcopies option. + * Add --trust, --untrust, and --semitrust options. + * get --from is the same as copy --from + * Bugfix: Fix fsck to not think all SHAnE keys are bad. + + -- Joey Hess Fri, 10 Jun 2011 11:48:40 -0400 + git-annex (0.20110601~bpo60+1) squeeze-backports; urgency=low * Minor bugfixes and error message improvements. diff --git a/doc/bugs/fsck_output.mdwn b/doc/bugs/fsck_output.mdwn index 3ded1b409e..90af1600d8 100644 --- a/doc/bugs/fsck_output.mdwn +++ b/doc/bugs/fsck_output.mdwn @@ -30,7 +30,7 @@ The newline is in the wrong place and confuses the user. It should be printed _a > A related problem occurs if an error message is unexpetedly printed. > Dummying up an example: > -> O get test1 (copying from foo...) E git-annex: failed to run ssh +> O get test1 (from foo...) E git-annex: failed to run ssh > failed > > --[[Joey]] diff --git a/doc/copies.mdwn b/doc/copies.mdwn index 39a714d3bb..16eba19c81 100644 --- a/doc/copies.mdwn +++ b/doc/copies.mdwn @@ -8,7 +8,8 @@ to keep N copies of a file's content available across all repositories. By default, N is 1; it is configured by annex.numcopies. This default can be overridden on a per-file-type basis by the annex.numcopies -setting in `.gitattributes` files. +setting in `.gitattributes` files. The --numcopies switch allows +temporarily using a different value. `git annex drop` attempts to check with other git remotes, to check that N copies of the file exist. If enough repositories cannot be verified to have diff --git a/doc/forum/incompatible_versions__63__.mdwn b/doc/forum/incompatible_versions__63__.mdwn new file mode 100644 index 0000000000..13eb181491 --- /dev/null +++ b/doc/forum/incompatible_versions__63__.mdwn @@ -0,0 +1 @@ +Are versions 0.14 and 0.20110522 incompatible? I can't seem to copy files from a system running 0.14 to one running 20110522. diff --git a/doc/forum/incompatible_versions__63__/comment_1_629f28258746d413e452cbd42a1a43f4._comment b/doc/forum/incompatible_versions__63__/comment_1_629f28258746d413e452cbd42a1a43f4._comment new file mode 100644 index 0000000000..3702fde6ea --- /dev/null +++ b/doc/forum/incompatible_versions__63__/comment_1_629f28258746d413e452cbd42a1a43f4._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="http://joey.kitenet.net/" + nickname="joey" + subject="comment 1" + date="2011-06-08T00:40:54Z" + content=""" +They are not. See [[upgrades]] +"""]] diff --git a/doc/forum/new_microfeatures.mdwn b/doc/forum/new_microfeatures.mdwn new file mode 100644 index 0000000000..683cc69b8b --- /dev/null +++ b/doc/forum/new_microfeatures.mdwn @@ -0,0 +1,53 @@ +I'm soliciting ideas for new small features that let git-annex do things that currently have to be done manually or whatever. + +Here are a few I've been considering: + +--- + +* --numcopies would be a useful command line switch. + > Update: Added. Also allows for things like `git annex drop --numcopies=2` when in a repo that normally needs 3 copies, if you need + > to urgently free up space. +* A way to make `drop` and other commands temporarily trust a given remote, or possibly all remotes. + +Combined, this would allow `git annex drop --numcopies=2 --trust=repoa --trust=repob` to remove files that have been replicated out to the other 2 repositories, which could be offline. (Slightly unsafe, but in this case the files are podcasts so not really.) + +> Update: done --[[Joey]] + +--- + +[[wishlist:_git-annex_replicate]] suggests some way for git-annex to have the smarts to copy content around on its own to ensure numcopies is satisfied. I'd be satisfied with a `git annex copy --to foo --if-needed-by-numcopies` + + > Contrary to the "basic" solution, I would love to have a git annex distribute which is smart enough to simply distribute all data according to certain rules. My ideal, personal use case during the next holidays where I will have two external disks, several SD cards with 32 GB each and a local disk with 20 GB (yes....) would be: + + cd ~/photos.annex # this repository does not have any objects! + git annex inject --bare /path/to/SD/card # this adds softlinks, but does **not** add anything to the index. it would calculate checksums (if enabled) and have to add a temporary location list, though + git annex distribute # this checks the config. it would see that my two external disks have a low cost whereas the two remotes have a higher cost. + # check numcopies. it's 3 + # copy to external disk one (cost x) + # copy to external disk two (cost x) + # copy to remote one (cost x * 2) + # remove file from temporary tracking list + git annex fsck # everything ok. yay! + +Come to think of it, the inject --bare thing is probably not a microfeature. Should I add a new wishlist item for that? -- RichiH + +> I've thought about such things before; does not seem really micro and I'm unsure how well it would work, but it would be worth a [[todo]]. --[[Joey]] + +--- + +Along similar lines, it might be nice to have a mode where git-annex tries to fill up a disk up to the `annex.diskreserve` with files, preferring files that have relatively few copies. Then as storage prices continue to fall, new large drives could just be plopped in and git-annex used to fill it up in a way that improves the overall redundancy without needing to manually pick and choose. + +--- + +If a remote could send on received files to another remote, I could use my own local bandwith efficiently while still having my git-annex repos replicate data. -- RichiH + +--- + +Really micro: + + % grep annex-push .git/config + annex-push = !git pull && git annex add . && git annex copy . --to origin --fast --quiet && git commit -a -m "$HOST $(date +%F--%H-%M-%S-%Z)" && git push + % + +-- RichiH +--[[Joey]] diff --git a/doc/forum/new_microfeatures/comment_1_058bd517c6fffaf3446b1f5d5be63623._comment b/doc/forum/new_microfeatures/comment_1_058bd517c6fffaf3446b1f5d5be63623._comment new file mode 100644 index 0000000000..84fdd325dc --- /dev/null +++ b/doc/forum/new_microfeatures/comment_1_058bd517c6fffaf3446b1f5d5be63623._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawkSq2FDpK2n66QRUxtqqdbyDuwgbQmUWus" + nickname="Jimmy" + subject="comment 1" + date="2011-06-01T17:36:50Z" + content=""" +I've been longing for an automated way of removing references to a remote assuming I know the exact uuid that I want to remove. i.e. I have lost a portable HDD due to a destructive process, I now want to delete all references to copies of data that was on that disk. Unless this feature exists, I would love to see it implemented. +"""]] diff --git a/doc/forum/new_microfeatures/comment_2_41ad904c68e89c85e1fc49c9e9106969._comment b/doc/forum/new_microfeatures/comment_2_41ad904c68e89c85e1fc49c9e9106969._comment new file mode 100644 index 0000000000..4451e20baf --- /dev/null +++ b/doc/forum/new_microfeatures/comment_2_41ad904c68e89c85e1fc49c9e9106969._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="http://joey.kitenet.net/" + nickname="joey" + subject="comment 2" + date="2011-06-01T20:24:33Z" + content=""" +@jimmy [[walkthrough/what_to_do_when_you_lose_a_repository]].. I have not seen a convincing argument that removing the location tracking data entirely serves any purpose +"""]] diff --git a/doc/forum/new_microfeatures/comment_3_a1a9347b5bc517f2a89a8b292c3f8517._comment b/doc/forum/new_microfeatures/comment_3_a1a9347b5bc517f2a89a8b292c3f8517._comment new file mode 100644 index 0000000000..4bb3aa684f --- /dev/null +++ b/doc/forum/new_microfeatures/comment_3_a1a9347b5bc517f2a89a8b292c3f8517._comment @@ -0,0 +1,15 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawnpdM9F8VbtQ_H5PaPMpGSxPe_d5L1eJ6w" + nickname="Rafaël" + subject="git annex unlock --readonly" + date="2011-06-02T11:34:42Z" + content=""" +This was already asked [here](http://bugs.debian.org/cgi-bin/bugreport.cgi?bug=606577), but I have a use case where I need to unlock with the files being hardlinked instead of copied (my fs does not support CoW), even though 'git annex lock' is now much faster ;-) . The idea is that 1) I want the external world see my repo \"as if\" it wasn't annexed (because of its own limitation to deal with soft links), and 2) I know what I do, and am sure that files won't be written to but only read. + +My case is: the repo contains a snapshot A1 of a certain remote directory. Later I want to rsync this dir into a new snapshot A2. Of course, I want to transfer only new or changed files, with the --copy-dest=A1 (or --compare-dest) rsync's options. Unfortunately, rsync won't recognize soft-links from git-annex, and will re-transfer everything. + + +Maybe I'm overusing git-annex ;-) but still, I find it is a legitimate use case, and even though there are workarounds (I don't even remember what I had to do), it would be much more straightforward to have 'git annex unlock --readonly' (or '--readonly-unsafe'?), ... or have rsync take soft-links into account, but I did not see the author ask for microfeatures ideas :) (it was discussed, and only some convoluted workarounds were proposed). Thanks. + + +"""]] diff --git a/doc/forum/new_microfeatures/comment_4_5a6786dc52382fff5cc42fdb05770196._comment b/doc/forum/new_microfeatures/comment_4_5a6786dc52382fff5cc42fdb05770196._comment new file mode 100644 index 0000000000..cc98109e6b --- /dev/null +++ b/doc/forum/new_microfeatures/comment_4_5a6786dc52382fff5cc42fdb05770196._comment @@ -0,0 +1,18 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawnpdM9F8VbtQ_H5PaPMpGSxPe_d5L1eJ6w" + nickname="Rafaël" + subject="git annex unused" + date="2011-06-02T11:55:58Z" + content=""" +Before dropping unsused items, sometimes I want to check the content of the files manually. +But currently, from e.g. a sha1 key, I don't know how to find the corresponding file, except with +'find .git/annex/objects -type f -name 'SHA1-s1678--70....', wich is too slow (I'm in the case where \"git log --stat -S'KEY'\" +won't work, either because it is too slow or it was never commited). By the way, +is it documented somewhere how to determine the 2 (nested) sub-directories in which a given +(by name) object is located? + +So I would like 'git-annex unused' be able to give me the list of *paths* to the unused items. +Also, I would really appreciate a command like 'git annex unused --log NUMBER [NUMBER2...]' which would do for me the suggested command +\"git log --stat -S'KEY'\", where NUMBER is from the 'git annex unused' output. +Thanks. +"""]] diff --git a/doc/forum/new_microfeatures/comment_5_3c627d275586ff499d928a8f8136babf._comment b/doc/forum/new_microfeatures/comment_5_3c627d275586ff499d928a8f8136babf._comment new file mode 100644 index 0000000000..f7361f5d1c --- /dev/null +++ b/doc/forum/new_microfeatures/comment_5_3c627d275586ff499d928a8f8136babf._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawnpdM9F8VbtQ_H5PaPMpGSxPe_d5L1eJ6w" + nickname="Rafaël" + subject="git annex unused" + date="2011-06-02T19:51:49Z" + content=""" +ps: concerning the command 'find .git/annex/objects -type f -name 'SHA1-s1678--70....' from my previous comment, it is \"significantly\" faster to search for the containing directory which have the same name: 'find .git/annex/objects -maxdepth 2 -mindepth 2 -type d -name 'SHA1-s1678--70....'. I am just curious: what is the need to have each file object in its own directory, itself nested under two more sub-directories? +"""]] diff --git a/doc/git-annex.mdwn b/doc/git-annex.mdwn index 7f2fce9d23..25f053af69 100644 --- a/doc/git-annex.mdwn +++ b/doc/git-annex.mdwn @@ -41,7 +41,7 @@ content from the key-value store. # sudo mount /media/usb # git remote add usbdrive /media/usb # git annex get video/hackity_hack_and_kaxxt.mov - get video/hackity_hack_and_kaxxt.mov (copying from usbdrive...) ok + get video/hackity_hack_and_kaxxt.mov (from usbdrive...) ok # git commit -a -m "got a video I want to rewatch on the plane" # git annex add iso @@ -354,6 +354,19 @@ Many git-annex commands will stage changes for later `git commit` by you. This option can be specified multiple times. +* --numcopies=n + + Overrides the `annex.numcopies` setting, forcing git-annex to ensure the + specified number of copies exist. + +* --trust=repository +* --semitrust=repository +* --untrust=repository + + Overrides trust settings for a repository. May be specified more than once. + + The repository should be specified using the name of a configured remote. + * --backend=name Specifies which key-value backend to use. This can be used when diff --git a/doc/install.mdwn b/doc/install.mdwn index 3d15eac604..7818aaf152 100644 --- a/doc/install.mdwn +++ b/doc/install.mdwn @@ -3,29 +3,32 @@ * [[OSX]] * [[Debian]] * [[Ubuntu]] +* [[Fedora]] ## Generic instructions To build and use git-annex, you will need: -* `git`: -* The Haskell Platform: -* MissingH: -* pcre-light: -* utf8-string: -* SHA: -* dataenc: -* TestPack -* QuickCheck 2 -* hS3 (optional, but recommended) -* `uuid`: - (or `uuidgen` from util-linux) -* `xargs`: -* `rsync`: -* `curl` : (optional, but recommended) -* `sha1sum`: (optional, but recommended) -* `gpg`: (optional; needed for encryption) -* [Ikiwiki](http://ikiwiki.info) is needed to build the documentation, - but that will be skipped if it is not installed. +* Haskell stuff + * [The Haskell Platform](http://haskell.org/platform/) + * [MissingH](http://github.com/jgoerzen/missingh/wiki) + * [pcre-light](http://hackage.haskell.org/package/pcre-light) + * [utf8-string](http://hackage.haskell.org/package/utf8-string) + * [SHA](http://hackage.haskell.org/package/SHA) + * [dataenc](http://hackage.haskell.org/package/dataenc) + * [TestPack](http://hackage.haskell.org/cgi-bin/hackage-scripts/package/testpack) + * [QuickCheck 2](http://hackage.haskell.org/package/QuickCheck) + * [hS3](http://hackage.haskell.org/package/hS3) (optional, but recommended) +* Shell commands + * [git](http://git-scm.com/) + * [uuid](http://www.ossp.org/pkg/lib/uuid/) + (or `uuidgen` from util-linux) + * [xargs](http://savannah.gnu.org/projects/findutils/) + * [rsync](http://rsync.samba.org/) + * [curl](http://http://curl.haxx.se/) (optional, but recommended) + * [sha1sum](ftp://ftp.gnu.org/gnu/coreutils/) (optional, but recommended; + a sha1 command will also do) + * [gpg](http://gnupg.org/) (optional; needed for encryption) + * [ikiwiki](http://ikiwiki.info) (optional; used to build the docs) Then just [[download]] git-annex and run: `make; make install` diff --git a/doc/install/Fedora.mdwn b/doc/install/Fedora.mdwn new file mode 100644 index 0000000000..0050295e86 --- /dev/null +++ b/doc/install/Fedora.mdwn @@ -0,0 +1,21 @@ +Installation recipe for Fedora 14. + +
+sudo yum install ghc cabal-install
+sudo cabal update
+sudo cabal install missingh
+sudo cabal install utf8-string
+sudo cabal install pcre-light
+sudo cabal install quickcheck
+sudo cabal install SHA
+sudo cabal install dataenc
+sudo cabal install hS3
+
+git clone git://git-annex.branchable.com/
+
+cd git-annex
+sudo make   # For some reason you need to use sudo here as otherwise the cabal installed packages doesn't seem to be there...
+sudo install git-annex
+
+ +Originally posted by Jon at --[[Joey]] diff --git a/doc/install/OSX.mdwn b/doc/install/OSX.mdwn index a6afd408bd..ba10071a16 100644 --- a/doc/install/OSX.mdwn +++ b/doc/install/OSX.mdwn @@ -7,11 +7,12 @@ sudo cabal install pcre-light sudo cabal install quickcheck sudo cabal install SHA sudo cabal install dataenc +sudo cabal install hS3 # stub S3 class (used if you don't have hS3 installed) has a bug, so you want to install this # optional: this will enable the gnu tools, (to give sha224sum etc..., it does not override the BSD userland) export PATH=$PATH:/opt/local/libexec/gnubin -git clone git://git.kitenet.net/git-annex +git clone git://git-annex.branchable.com/ cd git-annex make diff --git a/doc/install/Ubuntu.mdwn b/doc/install/Ubuntu.mdwn index ffc763ff31..afcf22b6d4 100644 --- a/doc/install/Ubuntu.mdwn +++ b/doc/install/Ubuntu.mdwn @@ -2,4 +2,4 @@ If using Ubuntu natty or newer: sudo apt-get install git-annex -Otherwise, see [[Debian]] manual installation instructions. +Otherwise, see [[manual_installation_instructions|install]]. diff --git a/doc/install/comment_2_cf0f829536744098d6846500db998b6a._comment b/doc/install/comment_2_cf0f829536744098d6846500db998b6a._comment index 134024908e..81d5a2c629 100644 --- a/doc/install/comment_2_cf0f829536744098d6846500db998b6a._comment +++ b/doc/install/comment_2_cf0f829536744098d6846500db998b6a._comment @@ -9,4 +9,9 @@ Because I haven't learned Cabal yet. But also because I've had bad experiences with both a) tying a particular program to a particular language's pet build system and then having to add ugliness when I later need to do something in the build that has nothing to do with that language and b) as a user, needing to deal with the pet build systems of languages when I just need to make some small change to the build process that is trivial in a Makefile. With that said, I do have a configure program written in Haskell, so at least it doesn't use autotools. :) + +Update: I did try using cabal, but git-annex includes 3 programs, and they +all link to a lot of git-annex modules, and cabal wanted to build nearly +every module 3 times, which was too slow for me and I could not find a way +around. """]] diff --git a/doc/news/version_0.20110610.mdwn b/doc/news/version_0.20110610.mdwn new file mode 100644 index 0000000000..9ab9e09076 --- /dev/null +++ b/doc/news/version_0.20110610.mdwn @@ -0,0 +1,6 @@ +git-annex 0.20110610 released with [[!toggle text="these changes"]] +[[!toggleable text=""" + * Add --numcopies option. + * Add --trust, --untrust, and --semitrust options. + * get --from is the same as copy --from + * Bugfix: Fix fsck to not think all SHAnE keys are bad."""]] \ No newline at end of file diff --git a/doc/trust.mdwn b/doc/trust.mdwn index 317e4b541f..7505a7af65 100644 --- a/doc/trust.mdwn +++ b/doc/trust.mdwn @@ -20,7 +20,9 @@ depended on to retain a copy of the file content; possibly the only [[copy|copies]]. (Being semitrusted is the default. The `git annex semitrust` command -restores a repository to this default, when it has been overridden.) +restores a repository to this default, when it has been overridden. +The `--semitrust` option can temporarily restore a repository to this +default.) ## untrusted @@ -42,7 +44,8 @@ archival drive, from which you rarely or never remove content. Deciding when it makes sense to trust the tracking info is up to you. One way to handle this is just to use `--force` when a command cannot -access a remote you trust. +access a remote you trust. Or to use `--trust` to specify a repisitory to +trust temporarily. -To configure a repository as fully trusted, use the `git annex trust` -command. +To configure a repository as fully and permanently trusted, +use the `git annex trust` command. diff --git a/doc/walkthrough/getting_file_content.mdwn b/doc/walkthrough/getting_file_content.mdwn index 5c899ee3c5..bf45fd97fd 100644 --- a/doc/walkthrough/getting_file_content.mdwn +++ b/doc/walkthrough/getting_file_content.mdwn @@ -8,8 +8,8 @@ USB drive. # cd /media/usb/annex # git pull laptop master # git annex get . - get my_cool_big_file (copying from laptop...) ok - get iso/debian.iso (copying from laptop...) ok + get my_cool_big_file (from laptop...) ok + get iso/debian.iso (from laptop...) ok Notice that you had to git pull from laptop first, this lets git-annex know what has changed in laptop, and so it knows about the files present there and diff --git a/doc/walkthrough/transferring_files:_When_things_go_wrong.mdwn b/doc/walkthrough/transferring_files:_When_things_go_wrong.mdwn index d8f0a19bd6..936d088f1f 100644 --- a/doc/walkthrough/transferring_files:_When_things_go_wrong.mdwn +++ b/doc/walkthrough/transferring_files:_When_things_go_wrong.mdwn @@ -14,5 +14,5 @@ it: failed # sudo mount /media/usb # git annex get video/hackity_hack_and_kaxxt.mov - get video/hackity_hack_and_kaxxt.mov (copying from usbdrive...) ok + get video/hackity_hack_and_kaxxt.mov (from usbdrive...) ok # git commit -a -m "got a video I want to rewatch on the plane" diff --git a/doc/walkthrough/using_ssh_remotes.mdwn b/doc/walkthrough/using_ssh_remotes.mdwn index 4c2f830de8..fbbbbe0701 100644 --- a/doc/walkthrough/using_ssh_remotes.mdwn +++ b/doc/walkthrough/using_ssh_remotes.mdwn @@ -12,7 +12,7 @@ to clone the laptop's annex to it: Now you can get files and they will be transferred (using `rsync` via `ssh`): # git annex get my_cool_big_file - get my_cool_big_file (getting UUID for origin...) (copying from origin...) + get my_cool_big_file (getting UUID for origin...) (from origin...) WORM-s2159-m1285650548--my_cool_big_file 100% 2159 2.1KB/s 00:00 ok diff --git a/git-annex-shell.hs b/git-annex-shell.hs index 940db71c34..55f34e1027 100644 --- a/git-annex-shell.hs +++ b/git-annex-shell.hs @@ -58,10 +58,9 @@ builtins :: [String] builtins = map cmdname cmds builtin :: String -> String -> [String] -> IO () -builtin cmd dir params = do - dir' <- Git.repoAbsPath dir - gitrepo <- Git.repoFromAbsPath dir' - dispatch gitrepo (cmd:(filterparams params)) cmds commonOptions header +builtin cmd dir params = + Git.repoAbsPath dir >>= Git.repoFromAbsPath >>= + dispatch (cmd:(filterparams params)) cmds commonOptions header external :: [String] -> IO () external params = do diff --git a/test.hs b/test.hs index 456c09060c..221607755a 100644 --- a/test.hs +++ b/test.hs @@ -31,7 +31,7 @@ import qualified Backend import qualified GitRepo as Git import qualified Locations import qualified Utility -import qualified BackendClass +import qualified Type.Backend import qualified Types import qualified GitAnnex import qualified LocationLog @@ -40,7 +40,7 @@ import qualified Trust import qualified Remote import qualified Content import qualified Command.DropUnused -import qualified Key +import qualified Type.Key import qualified Config import qualified Crypto