Merge branch 'master' into debian-stable

This commit is contained in:
Joey Hess 2011-06-10 12:01:19 -04:00
commit d8d4398e7c
60 changed files with 386 additions and 146 deletions

View file

@ -20,10 +20,12 @@ import Control.Monad.State
(liftIO, StateT, runStateT, evalStateT, liftM, get, put) (liftIO, StateT, runStateT, evalStateT, liftM, get, put)
import qualified GitRepo as Git import qualified GitRepo as Git
import qualified GitQueue import GitQueue
import qualified BackendClass import Types.Backend
import qualified RemoteClass import Types.Remote
import qualified CryptoTypes import Types.Crypto
import TrustLevel
import Types.UUID
-- git-annex's monad -- git-annex's monad
type Annex = StateT AnnexState IO type Annex = StateT AnnexState IO
@ -31,41 +33,45 @@ type Annex = StateT AnnexState IO
-- internal state storage -- internal state storage
data AnnexState = AnnexState data AnnexState = AnnexState
{ repo :: Git.Repo { repo :: Git.Repo
, backends :: [BackendClass.Backend Annex] , backends :: [Backend Annex]
, supportedBackends :: [BackendClass.Backend Annex] , supportedBackends :: [Backend Annex]
, remotes :: [RemoteClass.Remote Annex] , remotes :: [Remote Annex]
, repoqueue :: GitQueue.Queue , repoqueue :: Queue
, quiet :: Bool , quiet :: Bool
, force :: Bool , force :: Bool
, fast :: Bool , fast :: Bool
, forcebackend :: Maybe String , forcebackend :: Maybe String
, forcenumcopies :: Maybe Int
, defaultkey :: Maybe String , defaultkey :: Maybe String
, toremote :: Maybe String , toremote :: Maybe String
, fromremote :: Maybe String , fromremote :: Maybe String
, exclude :: [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 newState gitrepo allbackends = AnnexState
{ repo = gitrepo { repo = gitrepo
, backends = [] , backends = []
, remotes = [] , remotes = []
, supportedBackends = allbackends , supportedBackends = allbackends
, repoqueue = GitQueue.empty , repoqueue = empty
, quiet = False , quiet = False
, force = False , force = False
, fast = False , fast = False
, forcebackend = Nothing , forcebackend = Nothing
, forcenumcopies = Nothing
, defaultkey = Nothing , defaultkey = Nothing
, toremote = Nothing , toremote = Nothing
, fromremote = Nothing , fromremote = Nothing
, exclude = [] , exclude = []
, forcetrust = []
, cipher = Nothing , cipher = Nothing
} }
{- Create and returns an Annex state object for the specified git repo. -} {- 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 new gitrepo allbackends = do
gitrepo' <- liftIO $ Git.configRead gitrepo gitrepo' <- liftIO $ Git.configRead gitrepo
return $ newState gitrepo' allbackends return $ newState gitrepo' allbackends

View file

@ -42,8 +42,8 @@ import Locations
import qualified GitRepo as Git import qualified GitRepo as Git
import qualified Annex import qualified Annex
import Types import Types
import Key import Types.Key
import qualified BackendClass as B import qualified Types.Backend as B
import Messages import Messages
import Content import Content
import DataUnits import DataUnits

View file

@ -18,7 +18,7 @@ import Control.Monad.State (liftIO)
import Data.List import Data.List
import Data.String.Utils import Data.String.Utils
import BackendClass import Types.Backend
import LocationLog import LocationLog
import qualified Remote import qualified Remote
import qualified GitRepo as Git import qualified GitRepo as Git
@ -28,7 +28,7 @@ import Types
import UUID import UUID
import Messages import Messages
import Trust import Trust
import Key import Types.Key
backend :: Backend Annex backend :: Backend Annex
backend = Backend { backend = Backend {
@ -81,7 +81,7 @@ copyKeyFile key file = do
Left _ -> return False Left _ -> return False
else return True else return True
docopy r continue = do docopy r continue = do
showNote $ "copying from " ++ Remote.name r ++ "..." showNote $ "from " ++ Remote.name r ++ "..."
copied <- Remote.retrieveKeyFile r key file copied <- Remote.retrieveKeyFile r key file
if copied if copied
then return True then return True
@ -152,12 +152,16 @@ showTriedRemotes remotes =
showLongNote $ "Unable to access these remotes: " ++ showLongNote $ "Unable to access these remotes: " ++
(join ", " $ map Remote.name 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 :: Maybe Int -> Annex Int
getNumCopies (Just n) = return n getNumCopies v =
getNumCopies Nothing = do Annex.getState Annex.forcenumcopies >>= maybe (use v) (return . id)
g <- Annex.gitRepo
return $ read $ Git.configGet g config "1"
where where
use (Just n) = return n
use Nothing = do
g <- Annex.gitRepo
return $ read $ Git.configGet g config "1"
config = "annex.numcopies" config = "annex.numcopies"
{- Ideally, all keys have file size metadata. Old keys may not. -} {- Ideally, all keys have file size metadata. Old keys may not. -}

View file

@ -17,15 +17,15 @@ import System.Posix.Files
import System.FilePath import System.FilePath
import qualified Backend.File import qualified Backend.File
import BackendClass
import Messages import Messages
import qualified Annex import qualified Annex
import Locations import Locations
import Content import Content
import Types import Types
import Types.Backend
import Types.Key
import Utility import Utility
import qualified SysConfig import qualified SysConfig
import Key
type SHASize = Int type SHASize = Int
@ -119,7 +119,7 @@ checkKeyChecksum size key = do
then return True then return True
else do else do
s <- shaN size file s <- shaN size file
if s == keyName key if s == dropExtension (keyName key)
then return True then return True
else do else do
dest <- moveBad key dest <- moveBad key

View file

@ -10,10 +10,10 @@ module Backend.URL (backends) where
import Control.Monad.State (liftIO) import Control.Monad.State (liftIO)
import Types import Types
import BackendClass import Types.Backend
import Utility import Utility
import Messages import Messages
import Key import Types.Key
backends :: [Backend Annex] backends :: [Backend Annex]
backends = [backend] backends = [backend]

View file

@ -12,9 +12,9 @@ import System.FilePath
import System.Posix.Files import System.Posix.Files
import qualified Backend.File import qualified Backend.File
import BackendClass import Types.Backend
import Types import Types
import Key import Types.Key
backends :: [Backend Annex] backends :: [Backend Annex]
backends = [backend] backends = [backend]

View file

@ -28,8 +28,8 @@ import Messages
import UUID import UUID
{- Runs the passed command line. -} {- Runs the passed command line. -}
dispatch :: Git.Repo -> [String] -> [Command] -> [Option] -> String -> IO () dispatch :: [String] -> [Command] -> [Option] -> String -> Git.Repo -> IO ()
dispatch gitrepo args cmds options header = do dispatch args cmds options header gitrepo = do
setupConsole setupConsole
state <- Annex.new gitrepo allBackends state <- Annex.new gitrepo allBackends
(actions, state') <- Annex.run state $ parseCmd args header cmds options (actions, state') <- Annex.run state $ parseCmd args header cmds options

View file

@ -24,7 +24,7 @@ import qualified Annex
import qualified GitRepo as Git import qualified GitRepo as Git
import Locations import Locations
import Utility import Utility
import Key import Types.Key
{- A command runs in four stages. {- A command runs in four stages.
- -

View file

@ -22,7 +22,7 @@ import qualified Command.Move
import qualified Remote import qualified Remote
import qualified GitRepo as Git import qualified GitRepo as Git
import Backend import Backend
import Key import Types.Key
import Utility import Utility
type UnusedMap = M.Map String Key type UnusedMap = M.Map String Key

View file

@ -18,7 +18,7 @@ import Utility
import qualified Backend import qualified Backend
import Content import Content
import Messages import Messages
import Key import Types.Key
command :: [Command] command :: [Command]
command = [repoCommand "fromkey" paramPath seek command = [repoCommand "fromkey" paramPath seek

View file

@ -9,9 +9,12 @@ module Command.Get where
import Command import Command
import qualified Backend import qualified Backend
import qualified Annex
import qualified Remote
import Types import Types
import Content import Content
import Messages import Messages
import qualified Command.Move
command :: [Command] command :: [Command]
command = [repoCommand "get" paramPath seek command = [repoCommand "get" paramPath seek
@ -20,7 +23,6 @@ command = [repoCommand "get" paramPath seek
seek :: [CommandSeek] seek :: [CommandSeek]
seek = [withFilesInGit start] seek = [withFilesInGit start]
{- Gets an annexed file from one of the backends. -}
start :: CommandStartString start :: CommandStartString
start file = isAnnexed file $ \(key, backend) -> do start file = isAnnexed file $ \(key, backend) -> do
inannex <- inAnnex key inannex <- inAnnex key
@ -28,7 +30,12 @@ start file = isAnnexed file $ \(key, backend) -> do
then stop then stop
else do else do
showStart "get" file 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 Annex -> CommandPerform
perform key backend = do perform key backend = do

View file

@ -16,7 +16,7 @@ import Data.String.Utils
import Command import Command
import qualified Annex import qualified Annex
import qualified Remote import qualified Remote
import qualified RemoteClass import qualified Types.Remote as R
import qualified GitRepo as Git import qualified GitRepo as Git
import Utility import Utility
import Types 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 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 perform t u c = do
c' <- RemoteClass.setup t u c c' <- R.setup t u c
next $ cleanup u c' next $ cleanup u c'
cleanup :: UUID -> RemoteClass.RemoteConfig -> CommandCleanup cleanup :: UUID -> R.RemoteConfig -> CommandCleanup
cleanup u c = do cleanup u c = do
Remote.configSet u c Remote.configSet u c
g <- Annex.gitRepo g <- Annex.gitRepo
@ -73,7 +73,7 @@ cleanup u c = do
return True return True
{- Look up existing remote's UUID and config by name, or generate a new one -} {- 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 findByName name = do
m <- Remote.readRemoteLog m <- Remote.readRemoteLog
maybe generate return $ findByName' name m maybe generate return $ findByName' name m
@ -82,7 +82,7 @@ findByName name = do
uuid <- liftIO $ genUUID uuid <- liftIO $ genUUID
return (uuid, M.insert nameKey name M.empty) 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 findByName' n m = if null matches then Nothing else Just $ head matches
where where
matches = filter (matching . snd) $ M.toList m matches = filter (matching . snd) $ M.toList m
@ -98,14 +98,14 @@ remoteNames = do
return $ catMaybes $ map ((M.lookup nameKey) . snd) $ M.toList m return $ catMaybes $ map ((M.lookup nameKey) . snd) $ M.toList m
{- find the specified remote type -} {- 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 findType config = maybe unspecified specified $ M.lookup typeKey config
where where
unspecified = error "Specify the type of remote with type=" unspecified = error "Specify the type of remote with type="
specified s = case filter (findtype s) Remote.remoteTypes of specified s = case filter (findtype s) Remote.remoteTypes of
[] -> error $ "Unknown remote type " ++ s [] -> error $ "Unknown remote type " ++ s
(t:_) -> return t (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. -} {- The name of a configured remote is stored in its config using this key. -}
nameKey :: String nameKey :: String

View file

@ -14,8 +14,8 @@ import Data.List
import qualified Data.Map as M import qualified Data.Map as M
import qualified Annex import qualified Annex
import qualified BackendClass import qualified Types.Backend as B
import qualified RemoteClass import qualified Types.Remote as R
import qualified Remote import qualified Remote
import qualified Command.Unused import qualified Command.Unused
import qualified GitRepo as Git import qualified GitRepo as Git
@ -23,7 +23,7 @@ import Command
import Types import Types
import DataUnits import DataUnits
import Content import Content
import Key import Types.Key
import Locations import Locations
-- a named computation that produces a statistic -- a named computation that produces a statistic
@ -97,11 +97,11 @@ showStat s = calc =<< s
supported_backends :: Stat supported_backends :: Stat
supported_backends = stat "supported backends" $ supported_backends = stat "supported backends" $
lift (Annex.getState Annex.supportedBackends) >>= 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 = stat "supported remote types" $ 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 = stat "local annex size" $ local_annex_size = stat "local annex size" $

View file

@ -41,7 +41,7 @@ import qualified Annex
import qualified AnnexQueue import qualified AnnexQueue
import Utility import Utility
import StatFS import StatFS
import Key import Types.Key
import DataUnits import DataUnits
import Config import Config

View file

@ -43,11 +43,11 @@ import System.Exit
import System.Environment import System.Environment
import Types import Types
import Key import Types.Key
import RemoteClass import Types.Remote
import Utility import Utility
import Base64 import Base64
import CryptoTypes import Types.Crypto
{- The first half of a Cipher is used for HMAC; the remainder {- The first half of a Cipher is used for HMAC; the remainder
- is used as the GPG symmetric encryption passphrase. - is used as the GPG symmetric encryption passphrase.

View file

@ -13,7 +13,10 @@ import qualified GitRepo as Git
import CmdLine import CmdLine
import Command import Command
import Options import Options
import Utility
import TrustLevel
import qualified Annex import qualified Annex
import qualified Remote
import qualified Command.Add import qualified Command.Add
import qualified Command.Unannex import qualified Command.Unannex
@ -90,17 +93,24 @@ options = commonOptions ++
"specify from where to transfer content" "specify from where to transfer content"
, Option ['x'] ["exclude"] (ReqArg addexclude paramGlob) , Option ['x'] ["exclude"] (ReqArg addexclude paramGlob)
"skip files matching the glob pattern" "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 where
setkey v = Annex.changeState $ \s -> s { Annex.defaultkey = Just v }
setto v = Annex.changeState $ \s -> s { Annex.toremote = Just v } setto v = Annex.changeState $ \s -> s { Annex.toremote = Just v }
setfrom v = Annex.changeState $ \s -> s { Annex.fromremote = 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 :: String
header = "Usage: git-annex command [option ..]" header = "Usage: git-annex command [option ..]"
run :: [String] -> IO () run :: [String] -> IO ()
run args = do run args = dispatch args cmds options header =<< Git.repoFromCwd
gitrepo <- Git.repoFromCwd
dispatch gitrepo args cmds options header

View file

@ -36,7 +36,7 @@ import Word
import Data.Hash.MD5 import Data.Hash.MD5
import Types import Types
import Key import Types.Key
import qualified GitRepo as Git import qualified GitRepo as Git
{- Conventions: {- Conventions:

View file

@ -14,11 +14,13 @@ module Remote (
removeKey, removeKey,
hasKey, hasKey,
hasKeyCheap, hasKeyCheap,
keyPossibilities,
forceTrust,
remoteTypes, remoteTypes,
genList,
byName, byName,
nameToUUID, nameToUUID,
keyPossibilities,
remotesWithUUID, remotesWithUUID,
remotesWithoutUUID, remotesWithoutUUID,
@ -38,15 +40,15 @@ import qualified Data.Map as M
import Data.Maybe import Data.Maybe
import Data.Char import Data.Char
import RemoteClass
import Types import Types
import Types.Remote
import UUID import UUID
import qualified Annex import qualified Annex
import Trust
import LocationLog
import Locations import Locations
import Utility import Utility
import Config import Config
import Trust
import LocationLog
import qualified Remote.Git import qualified Remote.Git
import qualified Remote.S3 import qualified Remote.S3
@ -104,6 +106,14 @@ nameToUUID :: String -> Annex UUID
nameToUUID "." = getUUID =<< Annex.gitRepo -- special case for current repo nameToUUID "." = getUUID =<< Annex.gitRepo -- special case for current repo
nameToUUID n = liftM uuid (byName n) 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. {- 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 - Also returns a list of UUIDs that are trusted to have the key
@ -128,13 +138,11 @@ keyPossibilities key = do
return (sort validremotes, validtrusteduuids) return (sort validremotes, validtrusteduuids)
{- Filters a list of remotes to ones that have the listed uuids. -} forceTrust :: TrustLevel -> String -> Annex ()
remotesWithUUID :: [Remote Annex] -> [UUID] -> [Remote Annex] forceTrust level remotename = do
remotesWithUUID rs us = filter (\r -> uuid r `elem` us) rs r <- Remote.nameToUUID remotename
Annex.changeState $ \s ->
{- Filters a list of remotes to ones that do not have the listed uuids. -} s { Annex.forcetrust = (r, level):Annex.forcetrust s }
remotesWithoutUUID :: [Remote Annex] -> [UUID] -> [Remote Annex]
remotesWithoutUUID rs us = filter (\r -> uuid r `notElem` us) rs
{- Filename of remote.log. -} {- Filename of remote.log. -}
remoteLog :: Annex FilePath remoteLog :: Annex FilePath

View file

@ -19,8 +19,8 @@ import System.FilePath
import Data.List.Utils import Data.List.Utils
import System.Cmd.Utils import System.Cmd.Utils
import RemoteClass
import Types import Types
import Types.Remote
import qualified GitRepo as Git import qualified GitRepo as Git
import qualified Annex import qualified Annex
import UUID import UUID

View file

@ -16,8 +16,8 @@ import Control.Monad.State (liftIO)
import System.Directory hiding (copyFile) import System.Directory hiding (copyFile)
import System.FilePath import System.FilePath
import RemoteClass
import Types import Types
import Types.Remote
import qualified GitRepo as Git import qualified GitRepo as Git
import qualified Annex import qualified Annex
import UUID import UUID

View file

@ -11,7 +11,7 @@ import qualified Data.Map as M
import Control.Monad.State (liftIO) import Control.Monad.State (liftIO)
import Types import Types
import RemoteClass import Types.Remote
import Crypto import Crypto
import qualified Annex import qualified Annex
import Messages import Messages

View file

@ -12,8 +12,8 @@ import Control.Monad.State (liftIO)
import qualified Data.Map as M import qualified Data.Map as M
import System.Cmd.Utils import System.Cmd.Utils
import RemoteClass
import Types import Types
import Types.Remote
import qualified GitRepo as Git import qualified GitRepo as Git
import qualified Annex import qualified Annex
import qualified AnnexQueue import qualified AnnexQueue

View file

@ -18,8 +18,8 @@ import System.IO
import System.IO.Error (try) import System.IO.Error (try)
import System.Exit import System.Exit
import RemoteClass
import Types import Types
import Types.Remote
import qualified GitRepo as Git import qualified GitRepo as Git
import qualified Annex import qualified Annex
import UUID import UUID

View file

@ -16,8 +16,8 @@ import System.Directory
import System.Posix.Files import System.Posix.Files
import System.Posix.Process import System.Posix.Process
import RemoteClass
import Types import Types
import Types.Remote
import qualified GitRepo as Git import qualified GitRepo as Git
import qualified Annex import qualified Annex
import UUID import UUID

View file

@ -24,8 +24,9 @@ import System.Environment
import System.Posix.Files import System.Posix.Files
import System.Posix.Env (setEnv) import System.Posix.Env (setEnv)
import RemoteClass
import Types import Types
import Types.Remote
import Types.Key
import qualified GitRepo as Git import qualified GitRepo as Git
import qualified Annex import qualified Annex
import UUID import UUID
@ -35,7 +36,6 @@ import Config
import Remote.Special import Remote.Special
import Remote.Encryptable import Remote.Encryptable
import Crypto import Crypto
import Key
import Content import Content
import Base64 import Base64

View file

@ -13,7 +13,7 @@ import Data.String.Utils
import Control.Monad.State (liftIO) import Control.Monad.State (liftIO)
import Types import Types
import RemoteClass import Types.Remote
import qualified GitRepo as Git import qualified GitRepo as Git
import qualified Annex import qualified Annex
import UUID import UUID

View file

@ -1,4 +1,4 @@
{- git-annex trust levels {- git-annex trust
- -
- Copyright 2010 Joey Hess <joey@kitenet.net> - Copyright 2010 Joey Hess <joey@kitenet.net>
- -
@ -17,6 +17,7 @@ module Trust (
import Control.Monad.State import Control.Monad.State
import qualified Data.Map as M import qualified Data.Map as M
import TrustLevel
import qualified GitRepo as Git import qualified GitRepo as Git
import Types import Types
import UUID import UUID
@ -24,19 +25,6 @@ import Locations
import qualified Annex import qualified Annex
import Utility 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. -} {- Filename of trust.log. -}
trustLog :: Annex FilePath trustLog :: Annex FilePath
trustLog = do trustLog = do
@ -49,18 +37,20 @@ trustGet level = do
m <- trustMap m <- trustMap
return $ M.keys $ M.filter (== level) m 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 :: Annex (M.Map UUID TrustLevel)
trustMap = do trustMap = do
logfile <- trustLog logfile <- trustLog
overrides <- Annex.getState Annex.forcetrust
s <- liftIO $ catch (readFile logfile) ignoreerror s <- liftIO $ catch (readFile logfile) ignoreerror
return $ trustMapParse s return $ M.fromList $ trustMapParse s ++ overrides
where where
ignoreerror _ = return "" ignoreerror _ = return ""
{- Trust map parser. -} {- Trust map parser. -}
trustMapParse :: String -> M.Map UUID TrustLevel trustMapParse :: String -> [(UUID, TrustLevel)]
trustMapParse s = M.fromList $ map pair $ filter (not . null) $ lines s trustMapParse s = map pair $ filter (not . null) $ lines s
where where
pair l pair l
| length w > 1 = (w !! 0, read (w !! 1) :: TrustLevel) | length w > 1 = (w !! 0, read (w !! 1) :: TrustLevel)

23
TrustLevel.hs Normal file
View file

@ -0,0 +1,23 @@
{- git-annex trust levels
-
- Copyright 2010 Joey Hess <joey@kitenet.net>
-
- 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, "")]

View file

@ -11,6 +11,6 @@ module Types (
Key Key
) where ) where
import BackendClass
import Annex import Annex
import Key import Types.Backend
import Types.Key

View file

@ -7,9 +7,9 @@
- Licensed under the GNU GPL version 3 or higher. - 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 { data Backend a = Backend {
-- name of this backend -- name of this backend

View file

@ -5,7 +5,7 @@
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
module CryptoTypes where module Types.Crypto where
import Data.String.Utils import Data.String.Utils

View file

@ -1,11 +1,13 @@
{- git-annex Key data type {- git-annex Key data type
-
- Most things should not need this, using Types instead
- -
- Copyright 2011 Joey Hess <joey@kitenet.net> - Copyright 2011 Joey Hess <joey@kitenet.net>
- -
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
module Key ( module Types.Key (
Key(..), Key(..),
stubKey, stubKey,
readKey, readKey,

View file

@ -1,4 +1,4 @@
{- git-annex remotes class {- git-annex remotes types
- -
- Most things should not need this, using Remote instead - Most things should not need this, using Remote instead
- -
@ -7,13 +7,13 @@
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
module RemoteClass where module Types.Remote where
import Control.Exception import Control.Exception
import Data.Map as M import Data.Map as M
import qualified GitRepo as Git import qualified GitRepo as Git
import Key import Types.Key
type RemoteConfig = M.Map String String type RemoteConfig = M.Map String String

11
Types/UUID.hs Normal file
View file

@ -0,0 +1,11 @@
{- git-annex UUID type
-
- Copyright 2011 Joey Hess <joey@kitenet.net>
-
- 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

View file

@ -31,14 +31,13 @@ import Data.Maybe
import qualified GitRepo as Git import qualified GitRepo as Git
import Types import Types
import Types.UUID
import Locations import Locations
import qualified Annex import qualified Annex
import Utility import Utility
import qualified SysConfig import qualified SysConfig
import Config import Config
type UUID = String
configkey :: String configkey :: String
configkey = "annex.uuid" configkey = "annex.uuid"

View file

@ -18,7 +18,7 @@ import System.Posix.Types
import Data.Maybe import Data.Maybe
import Data.Char import Data.Char
import Key import Types.Key
import Content import Content
import Types import Types
import Locations import Locations

9
debian/changelog vendored
View file

@ -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 <joeyh@debian.org> Fri, 10 Jun 2011 11:48:40 -0400
git-annex (0.20110601~bpo60+1) squeeze-backports; urgency=low git-annex (0.20110601~bpo60+1) squeeze-backports; urgency=low
* Minor bugfixes and error message improvements. * Minor bugfixes and error message improvements.

View file

@ -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. > A related problem occurs if an error message is unexpetedly printed.
> Dummying up an example: > 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 > failed
> >
> --[[Joey]] > --[[Joey]]

View file

@ -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 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 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 `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 copies of the file exist. If enough repositories cannot be verified to have

View file

@ -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.

View file

@ -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]]
"""]]

View file

@ -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]]

View file

@ -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.
"""]]

View file

@ -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
"""]]

View file

@ -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.
"""]]

View file

@ -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.
"""]]

View file

@ -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?
"""]]

View file

@ -41,7 +41,7 @@ content from the key-value store.
# sudo mount /media/usb # sudo mount /media/usb
# git remote add usbdrive /media/usb # git remote add usbdrive /media/usb
# git annex get video/hackity_hack_and_kaxxt.mov # 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 commit -a -m "got a video I want to rewatch on the plane"
# git annex add iso # 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. 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 * --backend=name
Specifies which key-value backend to use. This can be used when Specifies which key-value backend to use. This can be used when

View file

@ -3,29 +3,32 @@
* [[OSX]] * [[OSX]]
* [[Debian]] * [[Debian]]
* [[Ubuntu]] * [[Ubuntu]]
* [[Fedora]]
## Generic instructions ## Generic instructions
To build and use git-annex, you will need: To build and use git-annex, you will need:
* `git`: <http://git-scm.com/> * Haskell stuff
* The Haskell Platform: <http://haskell.org/platform/> * [The Haskell Platform](http://haskell.org/platform/)
* MissingH: <http://github.com/jgoerzen/missingh/wiki> * [MissingH](http://github.com/jgoerzen/missingh/wiki)
* pcre-light: <http://hackage.haskell.org/package/pcre-light> * [pcre-light](http://hackage.haskell.org/package/pcre-light)
* utf8-string: <http://hackage.haskell.org/package/utf8-string> * [utf8-string](http://hackage.haskell.org/package/utf8-string)
* SHA: <http://hackage.haskell.org/package/SHA> * [SHA](http://hackage.haskell.org/package/SHA)
* dataenc: <http://hackage.haskell.org/package/dataenc> * [dataenc](http://hackage.haskell.org/package/dataenc)
* TestPack <http://hackage.haskell.org/cgi-bin/hackage-scripts/package/testpack> * [TestPack](http://hackage.haskell.org/cgi-bin/hackage-scripts/package/testpack)
* QuickCheck 2 <http://hackage.haskell.org/package/QuickCheck> * [QuickCheck 2](http://hackage.haskell.org/package/QuickCheck)
* hS3 <http://hackage.haskell.org/package/hS3> (optional, but recommended) * [hS3](http://hackage.haskell.org/package/hS3) (optional, but recommended)
* `uuid`: <http://www.ossp.org/pkg/lib/uuid/> * Shell commands
(or `uuidgen` from util-linux) * [git](http://git-scm.com/)
* `xargs`: <http://savannah.gnu.org/projects/findutils/> * [uuid](http://www.ossp.org/pkg/lib/uuid/)
* `rsync`: <http://rsync.samba.org/> (or `uuidgen` from util-linux)
* `curl` : <http://http://curl.haxx.se/> (optional, but recommended) * [xargs](http://savannah.gnu.org/projects/findutils/)
* `sha1sum`: <ftp://ftp.gnu.org/gnu/coreutils/> (optional, but recommended) * [rsync](http://rsync.samba.org/)
* `gpg`: <http://gnupg.org/> (optional; needed for encryption) * [curl](http://http://curl.haxx.se/) (optional, but recommended)
* [Ikiwiki](http://ikiwiki.info) is needed to build the documentation, * [sha1sum](ftp://ftp.gnu.org/gnu/coreutils/) (optional, but recommended;
but that will be skipped if it is not installed. 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` Then just [[download]] git-annex and run: `make; make install`

21
doc/install/Fedora.mdwn Normal file
View file

@ -0,0 +1,21 @@
Installation recipe for Fedora 14.
<pre>
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
</pre>
Originally posted by Jon at <https://gist.github.com/997568> --[[Joey]]

View file

@ -7,11 +7,12 @@ sudo cabal install pcre-light
sudo cabal install quickcheck sudo cabal install quickcheck
sudo cabal install SHA sudo cabal install SHA
sudo cabal install dataenc 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) # 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 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 cd git-annex
make make

View file

@ -2,4 +2,4 @@ If using Ubuntu natty or newer:
sudo apt-get install git-annex sudo apt-get install git-annex
Otherwise, see [[Debian]] manual installation instructions. Otherwise, see [[manual_installation_instructions|install]].

View file

@ -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. 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. :) 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.
"""]] """]]

View file

@ -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."""]]

View file

@ -20,7 +20,9 @@ depended on to retain a copy of the file content; possibly the only
[[copy|copies]]. [[copy|copies]].
(Being semitrusted is the default. The `git annex semitrust` command (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 ## 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. 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 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` To configure a repository as fully and permanently trusted,
command. use the `git annex trust` command.

View file

@ -8,8 +8,8 @@ USB drive.
# cd /media/usb/annex # cd /media/usb/annex
# git pull laptop master # git pull laptop master
# git annex get . # git annex get .
get my_cool_big_file (copying from laptop...) ok get my_cool_big_file (from laptop...) ok
get iso/debian.iso (copying 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 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 what has changed in laptop, and so it knows about the files present there and

View file

@ -14,5 +14,5 @@ it:
failed failed
# sudo mount /media/usb # sudo mount /media/usb
# git annex get video/hackity_hack_and_kaxxt.mov # 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 commit -a -m "got a video I want to rewatch on the plane"

View file

@ -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`): Now you can get files and they will be transferred (using `rsync` via `ssh`):
# git annex get my_cool_big_file # 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 WORM-s2159-m1285650548--my_cool_big_file 100% 2159 2.1KB/s 00:00
ok ok

View file

@ -58,10 +58,9 @@ builtins :: [String]
builtins = map cmdname cmds builtins = map cmdname cmds
builtin :: String -> String -> [String] -> IO () builtin :: String -> String -> [String] -> IO ()
builtin cmd dir params = do builtin cmd dir params =
dir' <- Git.repoAbsPath dir Git.repoAbsPath dir >>= Git.repoFromAbsPath >>=
gitrepo <- Git.repoFromAbsPath dir' dispatch (cmd:(filterparams params)) cmds commonOptions header
dispatch gitrepo (cmd:(filterparams params)) cmds commonOptions header
external :: [String] -> IO () external :: [String] -> IO ()
external params = do external params = do

View file

@ -31,7 +31,7 @@ import qualified Backend
import qualified GitRepo as Git import qualified GitRepo as Git
import qualified Locations import qualified Locations
import qualified Utility import qualified Utility
import qualified BackendClass import qualified Type.Backend
import qualified Types import qualified Types
import qualified GitAnnex import qualified GitAnnex
import qualified LocationLog import qualified LocationLog
@ -40,7 +40,7 @@ import qualified Trust
import qualified Remote import qualified Remote
import qualified Content import qualified Content
import qualified Command.DropUnused import qualified Command.DropUnused
import qualified Key import qualified Type.Key
import qualified Config import qualified Config
import qualified Crypto import qualified Crypto