Merge branch 'master' into encryption
This commit is contained in:
commit
2fcae0348f
81 changed files with 1671 additions and 221 deletions
176
Annex/Branch.hs
176
Annex/Branch.hs
|
@ -1,6 +1,6 @@
|
||||||
{- management of the git-annex branch
|
{- management of the git-annex branch
|
||||||
-
|
-
|
||||||
- Copyright 2011-2012 Joey Hess <joey@kitenet.net>
|
- Copyright 2011-2013 Joey Hess <joey@kitenet.net>
|
||||||
-
|
-
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
@ -22,9 +22,12 @@ module Annex.Branch (
|
||||||
commit,
|
commit,
|
||||||
files,
|
files,
|
||||||
withIndex,
|
withIndex,
|
||||||
|
performTransitions,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import qualified Data.ByteString.Lazy.Char8 as L
|
import qualified Data.ByteString.Lazy.Char8 as L
|
||||||
|
import qualified Data.Set as S
|
||||||
|
import qualified Data.Map as M
|
||||||
|
|
||||||
import Common.Annex
|
import Common.Annex
|
||||||
import Annex.BranchState
|
import Annex.BranchState
|
||||||
|
@ -32,6 +35,7 @@ import Annex.Journal
|
||||||
import qualified Git
|
import qualified Git
|
||||||
import qualified Git.Command
|
import qualified Git.Command
|
||||||
import qualified Git.Ref
|
import qualified Git.Ref
|
||||||
|
import qualified Git.Sha
|
||||||
import qualified Git.Branch
|
import qualified Git.Branch
|
||||||
import qualified Git.UnionMerge
|
import qualified Git.UnionMerge
|
||||||
import qualified Git.UpdateIndex
|
import qualified Git.UpdateIndex
|
||||||
|
@ -42,6 +46,12 @@ import Annex.CatFile
|
||||||
import Annex.Perms
|
import Annex.Perms
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import Utility.Env
|
import Utility.Env
|
||||||
|
import Logs
|
||||||
|
import Logs.Transitions
|
||||||
|
import Logs.Trust.Pure
|
||||||
|
import Annex.ReplaceFile
|
||||||
|
import qualified Annex.Queue
|
||||||
|
import Annex.Branch.Transitions
|
||||||
|
|
||||||
{- Name of the branch that is used to store git-annex's information. -}
|
{- Name of the branch that is used to store git-annex's information. -}
|
||||||
name :: Git.Ref
|
name :: Git.Ref
|
||||||
|
@ -110,6 +120,9 @@ forceUpdate = updateTo =<< siblingBranches
|
||||||
- later get staged, and might overwrite changes made during the merge.
|
- later get staged, and might overwrite changes made during the merge.
|
||||||
- This is only done if some of the Refs do need to be merged.
|
- This is only done if some of the Refs do need to be merged.
|
||||||
-
|
-
|
||||||
|
- Also handles performing any Transitions that have not yet been
|
||||||
|
- performed, in either the local branch, or the Refs.
|
||||||
|
-
|
||||||
- Returns True if any refs were merged in, False otherwise.
|
- Returns True if any refs were merged in, False otherwise.
|
||||||
-}
|
-}
|
||||||
updateTo :: [(Git.Ref, Git.Branch)] -> Annex Bool
|
updateTo :: [(Git.Ref, Git.Branch)] -> Annex Bool
|
||||||
|
@ -117,7 +130,8 @@ updateTo pairs = do
|
||||||
-- ensure branch exists, and get its current ref
|
-- ensure branch exists, and get its current ref
|
||||||
branchref <- getBranch
|
branchref <- getBranch
|
||||||
dirty <- journalDirty
|
dirty <- journalDirty
|
||||||
(refs, branches) <- unzip <$> filterM isnewer pairs
|
ignoredrefs <- getIgnoredRefs
|
||||||
|
(refs, branches) <- unzip <$> filterM (isnewer ignoredrefs) pairs
|
||||||
if null refs
|
if null refs
|
||||||
{- Even when no refs need to be merged, the index
|
{- Even when no refs need to be merged, the index
|
||||||
- may still be updated if the branch has gotten ahead
|
- may still be updated if the branch has gotten ahead
|
||||||
|
@ -132,7 +146,9 @@ updateTo pairs = do
|
||||||
else lockJournal $ go branchref dirty refs branches
|
else lockJournal $ go branchref dirty refs branches
|
||||||
return $ not $ null refs
|
return $ not $ null refs
|
||||||
where
|
where
|
||||||
isnewer (r, _) = inRepo $ Git.Branch.changed fullname r
|
isnewer ignoredrefs (r, _)
|
||||||
|
| S.member r ignoredrefs = return False
|
||||||
|
| otherwise = inRepo $ Git.Branch.changed fullname r
|
||||||
go branchref dirty refs branches = withIndex $ do
|
go branchref dirty refs branches = withIndex $ do
|
||||||
cleanjournal <- if dirty then stageJournal else return noop
|
cleanjournal <- if dirty then stageJournal else return noop
|
||||||
let merge_desc = if null branches
|
let merge_desc = if null branches
|
||||||
|
@ -140,23 +156,26 @@ updateTo pairs = do
|
||||||
else "merging " ++
|
else "merging " ++
|
||||||
unwords (map Git.Ref.describe branches) ++
|
unwords (map Git.Ref.describe branches) ++
|
||||||
" into " ++ show name
|
" into " ++ show name
|
||||||
|
localtransitions <- parseTransitionsStrictly "local"
|
||||||
|
<$> getStale transitionsLog
|
||||||
unless (null branches) $ do
|
unless (null branches) $ do
|
||||||
showSideAction merge_desc
|
showSideAction merge_desc
|
||||||
mergeIndex refs
|
mergeIndex refs
|
||||||
ff <- if dirty
|
let commitrefs = nub $ fullname:refs
|
||||||
then return False
|
unlessM (handleTransitions localtransitions commitrefs) $ do
|
||||||
else inRepo $ Git.Branch.fastForward fullname refs
|
ff <- if dirty
|
||||||
if ff
|
then return False
|
||||||
then updateIndex branchref
|
else inRepo $ Git.Branch.fastForward fullname refs
|
||||||
else commitBranch branchref merge_desc
|
if ff
|
||||||
(nub $ fullname:refs)
|
then updateIndex branchref
|
||||||
|
else commitBranch branchref merge_desc commitrefs
|
||||||
liftIO cleanjournal
|
liftIO cleanjournal
|
||||||
|
|
||||||
{- Gets the content of a file, which may be in the journal, or in the index
|
{- Gets the content of a file, which may be in the journal, or in the index
|
||||||
- (and committed to the branch).
|
- (and committed to the branch).
|
||||||
-
|
-
|
||||||
- Updates the branch if necessary, to ensure the most up-to-date available
|
- Updates the branch if necessary, to ensure the most up-to-date available
|
||||||
- content is available.
|
- content is returned.
|
||||||
-
|
-
|
||||||
- Returns an empty string if the file doesn't exist yet. -}
|
- Returns an empty string if the file doesn't exist yet. -}
|
||||||
get :: FilePath -> Annex String
|
get :: FilePath -> Annex String
|
||||||
|
@ -175,7 +194,10 @@ get' :: FilePath -> Annex String
|
||||||
get' file = go =<< getJournalFile file
|
get' file = go =<< getJournalFile file
|
||||||
where
|
where
|
||||||
go (Just journalcontent) = return journalcontent
|
go (Just journalcontent) = return journalcontent
|
||||||
go Nothing = withIndex $ L.unpack <$> catFile fullname file
|
go Nothing = getRaw file
|
||||||
|
|
||||||
|
getRaw :: FilePath -> Annex String
|
||||||
|
getRaw file = withIndex $ L.unpack <$> catFile fullname file
|
||||||
|
|
||||||
{- Applies a function to modifiy the content of a file.
|
{- Applies a function to modifiy the content of a file.
|
||||||
-
|
-
|
||||||
|
@ -225,7 +247,8 @@ commitBranch' branchref message parents = do
|
||||||
committedref <- inRepo $ Git.Branch.commit message fullname parents
|
committedref <- inRepo $ Git.Branch.commit message fullname parents
|
||||||
setIndexSha committedref
|
setIndexSha committedref
|
||||||
parentrefs <- commitparents <$> catObject committedref
|
parentrefs <- commitparents <$> catObject committedref
|
||||||
when (racedetected branchref parentrefs) $
|
when (racedetected branchref parentrefs) $ do
|
||||||
|
liftIO $ print ("race detected", branchref, parentrefs, "committing", (branchref, parents))
|
||||||
fixrace committedref parentrefs
|
fixrace committedref parentrefs
|
||||||
where
|
where
|
||||||
-- look for "parent ref" lines and return the refs
|
-- look for "parent ref" lines and return the refs
|
||||||
|
@ -253,13 +276,17 @@ commitBranch' branchref message parents = do
|
||||||
files :: Annex [FilePath]
|
files :: Annex [FilePath]
|
||||||
files = do
|
files = do
|
||||||
update
|
update
|
||||||
withIndex $ do
|
(++)
|
||||||
bfiles <- inRepo $ Git.Command.pipeNullSplitZombie
|
<$> branchFiles
|
||||||
[ Params "ls-tree --name-only -r -z"
|
<*> getJournalledFiles
|
||||||
, Param $ show fullname
|
|
||||||
]
|
{- Files in the branch, not including any from journalled changes,
|
||||||
jfiles <- getJournalledFiles
|
- and without updating the branch. -}
|
||||||
return $ jfiles ++ bfiles
|
branchFiles :: Annex [FilePath]
|
||||||
|
branchFiles = withIndex $ inRepo $ Git.Command.pipeNullSplitZombie
|
||||||
|
[ Params "ls-tree --name-only -r -z"
|
||||||
|
, Param $ show fullname
|
||||||
|
]
|
||||||
|
|
||||||
{- Populates the branch's index file with the current branch contents.
|
{- Populates the branch's index file with the current branch contents.
|
||||||
-
|
-
|
||||||
|
@ -361,3 +388,112 @@ stageJournal = withIndex $ do
|
||||||
sha <- hashFile h path
|
sha <- hashFile h path
|
||||||
streamer $ Git.UpdateIndex.updateIndexLine
|
streamer $ Git.UpdateIndex.updateIndexLine
|
||||||
sha FileBlob (asTopFilePath $ fileJournal file)
|
sha FileBlob (asTopFilePath $ fileJournal file)
|
||||||
|
|
||||||
|
{- This is run after the refs have been merged into the index,
|
||||||
|
- but before the result is committed to the branch.
|
||||||
|
- (Which is why it's passed the contents of the local branches's
|
||||||
|
- transition log before that merge took place.)
|
||||||
|
-
|
||||||
|
- When the refs contain transitions that have not yet been done locally,
|
||||||
|
- the transitions are performed on the index, and a new branch
|
||||||
|
- is created from the result.
|
||||||
|
-
|
||||||
|
- When there are transitions recorded locally that have not been done
|
||||||
|
- to the remote refs, the transitions are performed in the index,
|
||||||
|
- and committed to the existing branch. In this case, the untransitioned
|
||||||
|
- remote refs cannot be merged into the branch (since transitions
|
||||||
|
- throw away history), so they are added to the list of refs to ignore,
|
||||||
|
- to avoid re-merging content from them again.
|
||||||
|
-}
|
||||||
|
handleTransitions :: Transitions -> [Git.Ref] -> Annex Bool
|
||||||
|
handleTransitions localts refs = do
|
||||||
|
m <- M.fromList <$> mapM getreftransition refs
|
||||||
|
let remotets = M.elems m
|
||||||
|
if all (localts ==) remotets
|
||||||
|
then return False
|
||||||
|
else do
|
||||||
|
let allts = combineTransitions (localts:remotets)
|
||||||
|
let (transitionedrefs, untransitionedrefs) =
|
||||||
|
partition (\r -> M.lookup r m == Just allts) refs
|
||||||
|
performTransitions allts (localts /= allts) transitionedrefs
|
||||||
|
ignoreRefs untransitionedrefs
|
||||||
|
return True
|
||||||
|
where
|
||||||
|
getreftransition ref = do
|
||||||
|
ts <- parseTransitionsStrictly "remote" . L.unpack
|
||||||
|
<$> catFile ref transitionsLog
|
||||||
|
return (ref, ts)
|
||||||
|
|
||||||
|
ignoreRefs :: [Git.Ref] -> Annex ()
|
||||||
|
ignoreRefs rs = do
|
||||||
|
old <- getIgnoredRefs
|
||||||
|
let s = S.unions [old, S.fromList rs]
|
||||||
|
f <- fromRepo gitAnnexIgnoredRefs
|
||||||
|
replaceFile f $ \tmp -> liftIO $ writeFile tmp $
|
||||||
|
unlines $ map show $ S.elems s
|
||||||
|
|
||||||
|
getIgnoredRefs :: Annex (S.Set Git.Ref)
|
||||||
|
getIgnoredRefs = S.fromList . mapMaybe Git.Sha.extractSha . lines <$> content
|
||||||
|
where
|
||||||
|
content = do
|
||||||
|
f <- fromRepo gitAnnexIgnoredRefs
|
||||||
|
liftIO $ catchDefaultIO "" $ readFile f
|
||||||
|
|
||||||
|
{- Performs the specified transitions on the contents of the index file,
|
||||||
|
- commits it to the branch, or creates a new branch. -}
|
||||||
|
performTransitions :: Transitions -> Bool -> [Ref] -> Annex ()
|
||||||
|
performTransitions ts neednewlocalbranch transitionedrefs = do
|
||||||
|
-- For simplicity & speed, we're going to use the Annex.Queue to
|
||||||
|
-- update the git-annex branch, while it usually holds changes
|
||||||
|
-- for the head branch. Flush any such changes.
|
||||||
|
Annex.Queue.flush
|
||||||
|
withIndex $ do
|
||||||
|
run $ mapMaybe getTransitionCalculator $ transitionList ts
|
||||||
|
Annex.Queue.flush
|
||||||
|
if neednewlocalbranch
|
||||||
|
then do
|
||||||
|
committedref <- inRepo $ Git.Branch.commit message fullname transitionedrefs
|
||||||
|
setIndexSha committedref
|
||||||
|
else do
|
||||||
|
ref <- getBranch
|
||||||
|
commitBranch ref message (nub $ fullname:transitionedrefs)
|
||||||
|
where
|
||||||
|
message
|
||||||
|
| neednewlocalbranch && null transitionedrefs = "new branch for transition " ++ tdesc
|
||||||
|
| otherwise = "continuing transition " ++ tdesc
|
||||||
|
tdesc = show $ map describeTransition $ transitionList ts
|
||||||
|
|
||||||
|
{- The changes to make to the branch are calculated and applied to
|
||||||
|
- the branch directly, rather than going through the journal,
|
||||||
|
- which would be innefficient. (And the journal is not designed
|
||||||
|
- to hold changes to every file in the branch at once.)
|
||||||
|
-
|
||||||
|
- When a file in the branch is changed by transition code,
|
||||||
|
- that value is remembered and fed into the code for subsequent
|
||||||
|
- transitions.
|
||||||
|
-}
|
||||||
|
run [] = noop
|
||||||
|
run changers = do
|
||||||
|
trustmap <- calcTrustMap <$> getRaw trustLog
|
||||||
|
fs <- branchFiles
|
||||||
|
hasher <- inRepo hashObjectStart
|
||||||
|
forM_ fs $ \f -> do
|
||||||
|
content <- getRaw f
|
||||||
|
apply changers hasher f content trustmap
|
||||||
|
liftIO $ hashObjectStop hasher
|
||||||
|
apply [] _ _ _ _ = return ()
|
||||||
|
apply (changer:rest) hasher file content trustmap =
|
||||||
|
case changer file content trustmap of
|
||||||
|
RemoveFile -> do
|
||||||
|
Annex.Queue.addUpdateIndex
|
||||||
|
=<< inRepo (Git.UpdateIndex.unstageFile file)
|
||||||
|
-- File is deleted; can't run any other
|
||||||
|
-- transitions on it.
|
||||||
|
return ()
|
||||||
|
ChangeFile content' -> do
|
||||||
|
sha <- inRepo $ hashObject BlobObject content'
|
||||||
|
Annex.Queue.addUpdateIndex $ Git.UpdateIndex.pureStreamer $
|
||||||
|
Git.UpdateIndex.updateIndexLine sha FileBlob (asTopFilePath file)
|
||||||
|
apply rest hasher file content' trustmap
|
||||||
|
PreserveFile ->
|
||||||
|
apply rest hasher file content trustmap
|
||||||
|
|
53
Annex/Branch/Transitions.hs
Normal file
53
Annex/Branch/Transitions.hs
Normal file
|
@ -0,0 +1,53 @@
|
||||||
|
{- git-annex branch transitions
|
||||||
|
-
|
||||||
|
- Copyright 2013 Joey Hess <joey@kitenet.net>
|
||||||
|
-
|
||||||
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
|
-}
|
||||||
|
|
||||||
|
module Annex.Branch.Transitions (
|
||||||
|
FileTransition(..),
|
||||||
|
getTransitionCalculator
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Logs
|
||||||
|
import Logs.Transitions
|
||||||
|
import Logs.UUIDBased as UUIDBased
|
||||||
|
import Logs.Presence.Pure as Presence
|
||||||
|
import Types.TrustLevel
|
||||||
|
import Types.UUID
|
||||||
|
|
||||||
|
import qualified Data.Map as M
|
||||||
|
|
||||||
|
data FileTransition
|
||||||
|
= ChangeFile String
|
||||||
|
| RemoveFile
|
||||||
|
| PreserveFile
|
||||||
|
|
||||||
|
type TransitionCalculator = FilePath -> String -> TrustMap -> FileTransition
|
||||||
|
|
||||||
|
getTransitionCalculator :: Transition -> Maybe TransitionCalculator
|
||||||
|
getTransitionCalculator ForgetGitHistory = Nothing
|
||||||
|
getTransitionCalculator ForgetDeadRemotes = Just dropDead
|
||||||
|
|
||||||
|
dropDead :: FilePath -> String -> TrustMap -> FileTransition
|
||||||
|
dropDead f content trustmap = case getLogVariety f of
|
||||||
|
Just UUIDBasedLog -> ChangeFile $
|
||||||
|
UUIDBased.showLog id $ dropDeadFromUUIDBasedLog trustmap $ UUIDBased.parseLog Just content
|
||||||
|
Just (PresenceLog _) ->
|
||||||
|
let newlog = Presence.compactLog $ dropDeadFromPresenceLog trustmap $ Presence.parseLog content
|
||||||
|
in if null newlog
|
||||||
|
then RemoveFile
|
||||||
|
else ChangeFile $ Presence.showLog newlog
|
||||||
|
Nothing -> PreserveFile
|
||||||
|
|
||||||
|
dropDeadFromUUIDBasedLog :: TrustMap -> UUIDBased.Log String -> UUIDBased.Log String
|
||||||
|
dropDeadFromUUIDBasedLog trustmap = M.filterWithKey $ notDead trustmap . const
|
||||||
|
|
||||||
|
{- Presence logs can contain UUIDs or other values. Any line that matches
|
||||||
|
- a dead uuid is dropped; any other values are passed through. -}
|
||||||
|
dropDeadFromPresenceLog :: TrustMap -> [Presence.LogLine] -> [Presence.LogLine]
|
||||||
|
dropDeadFromPresenceLog trustmap = filter $ notDead trustmap (toUUID . Presence.info)
|
||||||
|
|
||||||
|
notDead :: TrustMap -> (v -> UUID) -> v -> Bool
|
||||||
|
notDead trustmap a v = M.findWithDefault SemiTrusted (a v) trustmap /= DeadTrusted
|
|
@ -279,6 +279,7 @@ moveAnnex key src = withObjectLoc key storeobject storedirect
|
||||||
then do
|
then do
|
||||||
updateInodeCache key src
|
updateInodeCache key src
|
||||||
replaceFile f $ liftIO . moveFile src
|
replaceFile f $ liftIO . moveFile src
|
||||||
|
chmodContent f
|
||||||
forM_ fs $
|
forM_ fs $
|
||||||
addContentWhenNotPresent key f
|
addContentWhenNotPresent key f
|
||||||
else ifM (goodContent key f)
|
else ifM (goodContent key f)
|
||||||
|
@ -500,6 +501,18 @@ freezeContent file = unlessM crippledFileSystem $
|
||||||
removeModes writeModes .
|
removeModes writeModes .
|
||||||
addModes [ownerReadMode]
|
addModes [ownerReadMode]
|
||||||
|
|
||||||
|
{- Adjusts read mode of annexed file per core.sharedRepository setting. -}
|
||||||
|
chmodContent :: FilePath -> Annex ()
|
||||||
|
chmodContent file = unlessM crippledFileSystem $
|
||||||
|
liftIO . go =<< fromRepo getSharedRepository
|
||||||
|
where
|
||||||
|
go GroupShared = modifyFileMode file $
|
||||||
|
addModes [ownerReadMode, groupReadMode]
|
||||||
|
go AllShared = modifyFileMode file $
|
||||||
|
addModes readModes
|
||||||
|
go _ = modifyFileMode file $
|
||||||
|
addModes [ownerReadMode]
|
||||||
|
|
||||||
{- Allows writing to an annexed file that freezeContent was called on
|
{- Allows writing to an annexed file that freezeContent was called on
|
||||||
- before. -}
|
- before. -}
|
||||||
thawContent :: FilePath -> Annex ()
|
thawContent :: FilePath -> Annex ()
|
||||||
|
|
|
@ -13,6 +13,7 @@ import qualified Annex.Branch
|
||||||
import qualified Git
|
import qualified Git
|
||||||
import qualified Git.Ref
|
import qualified Git.Ref
|
||||||
import qualified Git.Command
|
import qualified Git.Command
|
||||||
|
import qualified Git.Branch
|
||||||
import Utility.Base64
|
import Utility.Base64
|
||||||
|
|
||||||
{- Converts a git branch into a branch that is tagged with a UUID, typically
|
{- Converts a git branch into a branch that is tagged with a UUID, typically
|
||||||
|
@ -50,7 +51,10 @@ taggedPush :: UUID -> Maybe String -> Git.Ref -> Remote -> Git.Repo -> IO Bool
|
||||||
taggedPush u info branch remote = Git.Command.runBool
|
taggedPush u info branch remote = Git.Command.runBool
|
||||||
[ Param "push"
|
[ Param "push"
|
||||||
, Param $ Remote.name remote
|
, Param $ Remote.name remote
|
||||||
, Param $ refspec Annex.Branch.name
|
{- Using forcePush here is safe because we "own" the tagged branch
|
||||||
|
- we're pushing; it has no other writers. Ensures it is pushed
|
||||||
|
- even if it has been rewritten by a transition. -}
|
||||||
|
, Param $ Git.Branch.forcePush $ refspec Annex.Branch.name
|
||||||
, Param $ refspec branch
|
, Param $ refspec branch
|
||||||
]
|
]
|
||||||
where
|
where
|
||||||
|
|
52
Command/Forget.hs
Normal file
52
Command/Forget.hs
Normal file
|
@ -0,0 +1,52 @@
|
||||||
|
{- git-annex command
|
||||||
|
-
|
||||||
|
- Copyright 2013 Joey Hess <joey@kitenet.net>
|
||||||
|
-
|
||||||
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
|
-}
|
||||||
|
|
||||||
|
module Command.Forget where
|
||||||
|
|
||||||
|
import Common.Annex
|
||||||
|
import Command
|
||||||
|
import qualified Annex.Branch as Branch
|
||||||
|
import Logs.Transitions
|
||||||
|
import qualified Annex
|
||||||
|
import qualified Option
|
||||||
|
|
||||||
|
import Data.Time.Clock.POSIX
|
||||||
|
|
||||||
|
def :: [Command]
|
||||||
|
def = [withOptions forgetOptions $ command "forget" paramNothing seek
|
||||||
|
SectionMaintenance "prune git-annex branch history"]
|
||||||
|
|
||||||
|
forgetOptions :: [Option]
|
||||||
|
forgetOptions = [dropDeadOption]
|
||||||
|
|
||||||
|
dropDeadOption :: Option
|
||||||
|
dropDeadOption = Option.flag [] "drop-dead" "drop references to dead repositories"
|
||||||
|
|
||||||
|
seek :: [CommandSeek]
|
||||||
|
seek = [withFlag dropDeadOption $ \dropdead ->
|
||||||
|
withNothing $ start dropdead]
|
||||||
|
|
||||||
|
start :: Bool -> CommandStart
|
||||||
|
start dropdead = do
|
||||||
|
showStart "forget" "git-annex"
|
||||||
|
now <- liftIO getPOSIXTime
|
||||||
|
let basets = addTransition now ForgetGitHistory noTransitions
|
||||||
|
let ts = if dropdead
|
||||||
|
then addTransition now ForgetDeadRemotes basets
|
||||||
|
else basets
|
||||||
|
next $ perform ts =<< Annex.getState Annex.force
|
||||||
|
|
||||||
|
perform :: Transitions -> Bool -> CommandPerform
|
||||||
|
perform ts True = do
|
||||||
|
recordTransitions Branch.change ts
|
||||||
|
-- get branch committed before contining with the transition
|
||||||
|
Branch.update
|
||||||
|
void $ Branch.performTransitions ts True []
|
||||||
|
next $ return True
|
||||||
|
perform _ False = do
|
||||||
|
showLongNote "To forget git-annex branch history, you must specify --force. This deletes metadata!"
|
||||||
|
stop
|
|
@ -52,7 +52,9 @@ perform relaxed cache url = do
|
||||||
Just l | not (null l) -> do
|
Just l | not (null l) -> do
|
||||||
ok <- all id
|
ok <- all id
|
||||||
<$> mapM (downloadEnclosure relaxed cache) l
|
<$> mapM (downloadEnclosure relaxed cache) l
|
||||||
next $ cleanup url ok
|
unless ok $
|
||||||
|
feedProblem url "problem downloading item"
|
||||||
|
next $ cleanup url True
|
||||||
_ -> do
|
_ -> do
|
||||||
feedProblem url "bad feed content"
|
feedProblem url "bad feed content"
|
||||||
next $ return True
|
next $ return True
|
||||||
|
|
|
@ -17,7 +17,7 @@ import Data.Char
|
||||||
|
|
||||||
import Common.Annex
|
import Common.Annex
|
||||||
import Command
|
import Command
|
||||||
import qualified Logs.Location
|
import Logs
|
||||||
import qualified Logs.Presence
|
import qualified Logs.Presence
|
||||||
import Annex.CatFile
|
import Annex.CatFile
|
||||||
import qualified Annex.Branch
|
import qualified Annex.Branch
|
||||||
|
@ -135,7 +135,7 @@ getLog :: Key -> [CommandParam] -> Annex [String]
|
||||||
getLog key os = do
|
getLog key os = do
|
||||||
top <- fromRepo Git.repoPath
|
top <- fromRepo Git.repoPath
|
||||||
p <- liftIO $ relPathCwdToFile top
|
p <- liftIO $ relPathCwdToFile top
|
||||||
let logfile = p </> Logs.Location.logFile key
|
let logfile = p </> locationLogFile key
|
||||||
inRepo $ pipeNullSplitZombie $
|
inRepo $ pipeNullSplitZombie $
|
||||||
[ Params "log -z --pretty=format:%ct --raw --abbrev=40"
|
[ Params "log -z --pretty=format:%ct --raw --abbrev=40"
|
||||||
, Param "--remove-empty"
|
, Param "--remove-empty"
|
||||||
|
|
|
@ -167,29 +167,45 @@ pushRemote remote branch = go =<< needpush
|
||||||
showOutput
|
showOutput
|
||||||
inRepo $ pushBranch remote branch
|
inRepo $ pushBranch remote branch
|
||||||
|
|
||||||
{- If the remote is a bare git repository, it's best to push the branch
|
{- Pushes a regular branch like master to a remote. Also pushes the git-annex
|
||||||
- directly to it. On the other hand, if it's not bare, pushing to the
|
- branch.
|
||||||
- checked out branch will fail, and this is why we use the syncBranch.
|
-
|
||||||
|
- If the remote is a bare git repository, it's best to push the regular
|
||||||
|
- branch directly to it, so that cloning/pulling will get it.
|
||||||
|
- On the other hand, if it's not bare, pushing to the checked out branch
|
||||||
|
- will fail, and this is why we push to its syncBranch.
|
||||||
-
|
-
|
||||||
- Git offers no way to tell if a remote is bare or not, so both methods
|
- Git offers no way to tell if a remote is bare or not, so both methods
|
||||||
- are tried.
|
- are tried.
|
||||||
-
|
-
|
||||||
- The direct push is likely to spew an ugly error message, so stderr is
|
- The direct push is likely to spew an ugly error message, so stderr is
|
||||||
- elided. Since progress is output to stderr too, the sync push is done
|
- elided. Since git progress display goes to stderr too, the sync push
|
||||||
- first, and actually sends the data. Then the direct push is tried,
|
- is done first, and actually sends the data. Then the direct push is
|
||||||
- with stderr discarded, to update the branch ref on the remote.
|
- tried, with stderr discarded, to update the branch ref on the remote.
|
||||||
|
-
|
||||||
|
- The sync push forces the update of the remote synced/git-annex branch.
|
||||||
|
- This is necessary if a transition has rewritten the git-annex branch.
|
||||||
|
- Normally any changes to the git-annex branch get pulled and merged before
|
||||||
|
- this push, so this forcing is unlikely to overwrite new data pushed
|
||||||
|
- in from another repository that is also syncing.
|
||||||
|
-
|
||||||
|
- But overwriting of data on synced/git-annex can happen, in a race.
|
||||||
|
- The only difference caused by using a forced push in that case is that
|
||||||
|
- the last repository to push wins the race, rather than the first to push.
|
||||||
-}
|
-}
|
||||||
pushBranch :: Remote -> Git.Ref -> Git.Repo -> IO Bool
|
pushBranch :: Remote -> Git.Ref -> Git.Repo -> IO Bool
|
||||||
pushBranch remote branch g = tryIO directpush `after` syncpush
|
pushBranch remote branch g = tryIO (directpush g) `after` syncpush g
|
||||||
where
|
where
|
||||||
syncpush = Git.Command.runBool (pushparams (refspec branch)) g
|
syncpush = Git.Command.runBool $ pushparams
|
||||||
directpush = Git.Command.runQuiet (pushparams (show $ Git.Ref.base branch)) g
|
[ Git.Branch.forcePush $ refspec Annex.Branch.name
|
||||||
pushparams b =
|
, refspec branch
|
||||||
|
]
|
||||||
|
directpush = Git.Command.runQuiet $ pushparams
|
||||||
|
[show $ Git.Ref.base branch]
|
||||||
|
pushparams branches =
|
||||||
[ Param "push"
|
[ Param "push"
|
||||||
, Param $ Remote.name remote
|
, Param $ Remote.name remote
|
||||||
, Param $ refspec Annex.Branch.name
|
] ++ map Param branches
|
||||||
, Param b
|
|
||||||
]
|
|
||||||
refspec b = concat
|
refspec b = concat
|
||||||
[ show $ Git.Ref.base b
|
[ show $ Git.Ref.base b
|
||||||
, ":"
|
, ":"
|
||||||
|
|
|
@ -101,3 +101,7 @@ commit message branch parentrefs repo = do
|
||||||
return sha
|
return sha
|
||||||
where
|
where
|
||||||
ps = concatMap (\r -> ["-p", show r]) parentrefs
|
ps = concatMap (\r -> ["-p", show r]) parentrefs
|
||||||
|
|
||||||
|
{- A leading + makes git-push force pushing a branch. -}
|
||||||
|
forcePush :: String -> String
|
||||||
|
forcePush b = "+" ++ b
|
||||||
|
|
|
@ -67,6 +67,7 @@ import qualified Command.Map
|
||||||
import qualified Command.Direct
|
import qualified Command.Direct
|
||||||
import qualified Command.Indirect
|
import qualified Command.Indirect
|
||||||
import qualified Command.Upgrade
|
import qualified Command.Upgrade
|
||||||
|
import qualified Command.Forget
|
||||||
import qualified Command.Version
|
import qualified Command.Version
|
||||||
import qualified Command.Help
|
import qualified Command.Help
|
||||||
#ifdef WITH_ASSISTANT
|
#ifdef WITH_ASSISTANT
|
||||||
|
@ -139,6 +140,7 @@ cmds = concat
|
||||||
, Command.Direct.def
|
, Command.Direct.def
|
||||||
, Command.Indirect.def
|
, Command.Indirect.def
|
||||||
, Command.Upgrade.def
|
, Command.Upgrade.def
|
||||||
|
, Command.Forget.def
|
||||||
, Command.Version.def
|
, Command.Version.def
|
||||||
, Command.Help.def
|
, Command.Help.def
|
||||||
#ifdef WITH_ASSISTANT
|
#ifdef WITH_ASSISTANT
|
||||||
|
|
|
@ -35,6 +35,7 @@ module Locations (
|
||||||
gitAnnexJournalLock,
|
gitAnnexJournalLock,
|
||||||
gitAnnexIndex,
|
gitAnnexIndex,
|
||||||
gitAnnexIndexLock,
|
gitAnnexIndexLock,
|
||||||
|
gitAnnexIgnoredRefs,
|
||||||
gitAnnexPidFile,
|
gitAnnexPidFile,
|
||||||
gitAnnexDaemonStatusFile,
|
gitAnnexDaemonStatusFile,
|
||||||
gitAnnexLogFile,
|
gitAnnexLogFile,
|
||||||
|
@ -225,6 +226,10 @@ gitAnnexIndex r = gitAnnexDir r </> "index"
|
||||||
gitAnnexIndexLock :: Git.Repo -> FilePath
|
gitAnnexIndexLock :: Git.Repo -> FilePath
|
||||||
gitAnnexIndexLock r = gitAnnexDir r </> "index.lck"
|
gitAnnexIndexLock r = gitAnnexDir r </> "index.lck"
|
||||||
|
|
||||||
|
{- List of refs that should not be merged into the git-annex branch. -}
|
||||||
|
gitAnnexIgnoredRefs :: Git.Repo -> FilePath
|
||||||
|
gitAnnexIgnoredRefs r = gitAnnexDir r </> "ignoredrefs"
|
||||||
|
|
||||||
{- Pid file for daemon mode. -}
|
{- Pid file for daemon mode. -}
|
||||||
gitAnnexPidFile :: Git.Repo -> FilePath
|
gitAnnexPidFile :: Git.Repo -> FilePath
|
||||||
gitAnnexPidFile r = gitAnnexDir r </> "daemon.pid"
|
gitAnnexPidFile r = gitAnnexDir r </> "daemon.pid"
|
||||||
|
|
110
Logs.hs
Normal file
110
Logs.hs
Normal file
|
@ -0,0 +1,110 @@
|
||||||
|
{- git-annex log file names
|
||||||
|
-
|
||||||
|
- Copyright 2013 Joey Hess <joey@kitenet.net>
|
||||||
|
-
|
||||||
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
|
-}
|
||||||
|
|
||||||
|
module Logs where
|
||||||
|
|
||||||
|
import Common.Annex
|
||||||
|
import Types.Key
|
||||||
|
|
||||||
|
data LogVariety = UUIDBasedLog | PresenceLog Key
|
||||||
|
deriving (Show)
|
||||||
|
|
||||||
|
{- Converts a path from the git-annex branch into one of the varieties
|
||||||
|
- of logs used by git-annex, if it's a known path. -}
|
||||||
|
getLogVariety :: FilePath -> Maybe LogVariety
|
||||||
|
getLogVariety f
|
||||||
|
| f `elem` uuidBasedLogs = Just UUIDBasedLog
|
||||||
|
| otherwise = PresenceLog <$> firstJust (presenceLogs f)
|
||||||
|
|
||||||
|
{- All the uuid-based logs stored in the git-annex branch. -}
|
||||||
|
uuidBasedLogs :: [FilePath]
|
||||||
|
uuidBasedLogs =
|
||||||
|
[ uuidLog
|
||||||
|
, remoteLog
|
||||||
|
, trustLog
|
||||||
|
, groupLog
|
||||||
|
, preferredContentLog
|
||||||
|
]
|
||||||
|
|
||||||
|
{- All the ways to get a key from a presence log file -}
|
||||||
|
presenceLogs :: FilePath -> [Maybe Key]
|
||||||
|
presenceLogs f =
|
||||||
|
[ urlLogFileKey f
|
||||||
|
, locationLogFileKey f
|
||||||
|
]
|
||||||
|
|
||||||
|
uuidLog :: FilePath
|
||||||
|
uuidLog = "uuid.log"
|
||||||
|
|
||||||
|
remoteLog :: FilePath
|
||||||
|
remoteLog = "remote.log"
|
||||||
|
|
||||||
|
trustLog :: FilePath
|
||||||
|
trustLog = "trust.log"
|
||||||
|
|
||||||
|
groupLog :: FilePath
|
||||||
|
groupLog = "group.log"
|
||||||
|
|
||||||
|
preferredContentLog :: FilePath
|
||||||
|
preferredContentLog = "preferred-content.log"
|
||||||
|
|
||||||
|
{- The pathname of the location log file for a given key. -}
|
||||||
|
locationLogFile :: Key -> String
|
||||||
|
locationLogFile key = hashDirLower key ++ keyFile key ++ ".log"
|
||||||
|
|
||||||
|
{- Converts a pathname into a key if it's a location log. -}
|
||||||
|
locationLogFileKey :: FilePath -> Maybe Key
|
||||||
|
locationLogFileKey path
|
||||||
|
| ["remote", "web"] `isPrefixOf` splitDirectories dir = Nothing
|
||||||
|
| ext == ".log" = fileKey base
|
||||||
|
| otherwise = Nothing
|
||||||
|
where
|
||||||
|
(dir, file) = splitFileName path
|
||||||
|
(base, ext) = splitAt (length file - 4) file
|
||||||
|
|
||||||
|
{- The filename of the url log for a given key. -}
|
||||||
|
urlLogFile :: Key -> FilePath
|
||||||
|
urlLogFile key = hashDirLower key </> keyFile key ++ urlLogExt
|
||||||
|
|
||||||
|
{- Old versions stored the urls elsewhere. -}
|
||||||
|
oldurlLogs :: Key -> [FilePath]
|
||||||
|
oldurlLogs key =
|
||||||
|
[ "remote/web" </> hashDirLower key </> key2file key ++ ".log"
|
||||||
|
, "remote/web" </> hashDirLower key </> keyFile key ++ ".log"
|
||||||
|
]
|
||||||
|
|
||||||
|
urlLogExt :: String
|
||||||
|
urlLogExt = ".log.web"
|
||||||
|
|
||||||
|
{- Converts a url log file into a key.
|
||||||
|
- (Does not work on oldurlLogs.) -}
|
||||||
|
urlLogFileKey :: FilePath -> Maybe Key
|
||||||
|
urlLogFileKey path
|
||||||
|
| ext == urlLogExt = fileKey base
|
||||||
|
| otherwise = Nothing
|
||||||
|
where
|
||||||
|
file = takeFileName path
|
||||||
|
(base, ext) = splitAt (length file - extlen) file
|
||||||
|
extlen = length urlLogExt
|
||||||
|
|
||||||
|
{- Does not work on oldurllogs. -}
|
||||||
|
isUrlLog :: FilePath -> Bool
|
||||||
|
isUrlLog file = urlLogExt `isSuffixOf` file
|
||||||
|
|
||||||
|
prop_logs_sane :: Key -> Bool
|
||||||
|
prop_logs_sane dummykey = all id
|
||||||
|
[ isNothing (getLogVariety "unknown")
|
||||||
|
, expect isUUIDBasedLog (getLogVariety uuidLog)
|
||||||
|
, expect isPresenceLog (getLogVariety $ locationLogFile dummykey)
|
||||||
|
, expect isPresenceLog (getLogVariety $ urlLogFile dummykey)
|
||||||
|
]
|
||||||
|
where
|
||||||
|
expect = maybe False
|
||||||
|
isUUIDBasedLog UUIDBasedLog = True
|
||||||
|
isUUIDBasedLog _ = False
|
||||||
|
isPresenceLog (PresenceLog k) = k == dummykey
|
||||||
|
isPresenceLog _ = False
|
|
@ -21,16 +21,13 @@ import qualified Data.Set as S
|
||||||
import Data.Time.Clock.POSIX
|
import Data.Time.Clock.POSIX
|
||||||
|
|
||||||
import Common.Annex
|
import Common.Annex
|
||||||
|
import Logs
|
||||||
import qualified Annex.Branch
|
import qualified Annex.Branch
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import Logs.UUIDBased
|
import Logs.UUIDBased
|
||||||
import Types.Group
|
import Types.Group
|
||||||
import Types.StandardGroups
|
import Types.StandardGroups
|
||||||
|
|
||||||
{- Filename of group.log. -}
|
|
||||||
groupLog :: FilePath
|
|
||||||
groupLog = "group.log"
|
|
||||||
|
|
||||||
{- Returns the groups of a given repo UUID. -}
|
{- Returns the groups of a given repo UUID. -}
|
||||||
lookupGroups :: UUID -> Annex (S.Set Group)
|
lookupGroups :: UUID -> Annex (S.Set Group)
|
||||||
lookupGroups u = (fromMaybe S.empty . M.lookup u) . groupsByUUID <$> groupMap
|
lookupGroups u = (fromMaybe S.empty . M.lookup u) . groupsByUUID <$> groupMap
|
||||||
|
|
|
@ -20,12 +20,11 @@ module Logs.Location (
|
||||||
loggedLocations,
|
loggedLocations,
|
||||||
loggedKeys,
|
loggedKeys,
|
||||||
loggedKeysFor,
|
loggedKeysFor,
|
||||||
logFile,
|
|
||||||
logFileKey
|
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Common.Annex
|
import Common.Annex
|
||||||
import qualified Annex.Branch
|
import qualified Annex.Branch
|
||||||
|
import Logs
|
||||||
import Logs.Presence
|
import Logs.Presence
|
||||||
import Annex.UUID
|
import Annex.UUID
|
||||||
|
|
||||||
|
@ -37,19 +36,19 @@ logStatus key status = do
|
||||||
|
|
||||||
{- Log a change in the presence of a key's value in a repository. -}
|
{- Log a change in the presence of a key's value in a repository. -}
|
||||||
logChange :: Key -> UUID -> LogStatus -> Annex ()
|
logChange :: Key -> UUID -> LogStatus -> Annex ()
|
||||||
logChange key (UUID u) s = addLog (logFile key) =<< logNow s u
|
logChange key (UUID u) s = addLog (locationLogFile key) =<< logNow s u
|
||||||
logChange _ NoUUID _ = noop
|
logChange _ NoUUID _ = noop
|
||||||
|
|
||||||
{- Returns a list of repository UUIDs that, according to the log, have
|
{- Returns a list of repository UUIDs that, according to the log, have
|
||||||
- the value of a key.
|
- the value of a key.
|
||||||
-}
|
-}
|
||||||
loggedLocations :: Key -> Annex [UUID]
|
loggedLocations :: Key -> Annex [UUID]
|
||||||
loggedLocations key = map toUUID <$> (currentLog . logFile) key
|
loggedLocations key = map toUUID <$> (currentLog . locationLogFile) key
|
||||||
|
|
||||||
{- Finds all keys that have location log information.
|
{- Finds all keys that have location log information.
|
||||||
- (There may be duplicate keys in the list.) -}
|
- (There may be duplicate keys in the list.) -}
|
||||||
loggedKeys :: Annex [Key]
|
loggedKeys :: Annex [Key]
|
||||||
loggedKeys = mapMaybe (logFileKey . takeFileName) <$> Annex.Branch.files
|
loggedKeys = mapMaybe locationLogFileKey <$> Annex.Branch.files
|
||||||
|
|
||||||
{- Finds all keys that have location log information indicating
|
{- Finds all keys that have location log information indicating
|
||||||
- they are present for the specified repository. -}
|
- they are present for the specified repository. -}
|
||||||
|
@ -62,15 +61,3 @@ loggedKeysFor u = filterM isthere =<< loggedKeys
|
||||||
us <- loggedLocations k
|
us <- loggedLocations k
|
||||||
let !there = u `elem` us
|
let !there = u `elem` us
|
||||||
return there
|
return there
|
||||||
|
|
||||||
{- The filename of the log file for a given key. -}
|
|
||||||
logFile :: Key -> String
|
|
||||||
logFile key = hashDirLower key ++ keyFile key ++ ".log"
|
|
||||||
|
|
||||||
{- Converts a log filename into a key. -}
|
|
||||||
logFileKey :: FilePath -> Maybe Key
|
|
||||||
logFileKey file
|
|
||||||
| ext == ".log" = fileKey base
|
|
||||||
| otherwise = Nothing
|
|
||||||
where
|
|
||||||
(base, ext) = splitAt (length file - 4) file
|
|
||||||
|
|
|
@ -24,6 +24,7 @@ import Data.Time.Clock.POSIX
|
||||||
import Common.Annex
|
import Common.Annex
|
||||||
import qualified Annex.Branch
|
import qualified Annex.Branch
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
|
import Logs
|
||||||
import Logs.UUIDBased
|
import Logs.UUIDBased
|
||||||
import Limit
|
import Limit
|
||||||
import qualified Utility.Matcher
|
import qualified Utility.Matcher
|
||||||
|
@ -35,10 +36,6 @@ import Logs.Group
|
||||||
import Logs.Remote
|
import Logs.Remote
|
||||||
import Types.StandardGroups
|
import Types.StandardGroups
|
||||||
|
|
||||||
{- Filename of preferred-content.log. -}
|
|
||||||
preferredContentLog :: FilePath
|
|
||||||
preferredContentLog = "preferred-content.log"
|
|
||||||
|
|
||||||
{- Changes the preferred content configuration of a remote. -}
|
{- Changes the preferred content configuration of a remote. -}
|
||||||
preferredContentSet :: UUID -> String -> Annex ()
|
preferredContentSet :: UUID -> String -> Annex ()
|
||||||
preferredContentSet uuid@(UUID _) val = do
|
preferredContentSet uuid@(UUID _) val = do
|
||||||
|
|
|
@ -12,36 +12,18 @@
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Logs.Presence (
|
module Logs.Presence (
|
||||||
LogStatus(..),
|
module X,
|
||||||
LogLine(LogLine),
|
|
||||||
addLog,
|
addLog,
|
||||||
readLog,
|
readLog,
|
||||||
getLog,
|
|
||||||
parseLog,
|
|
||||||
showLog,
|
|
||||||
logNow,
|
logNow,
|
||||||
compactLog,
|
currentLog
|
||||||
currentLog,
|
|
||||||
prop_parse_show_log,
|
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Data.Time.Clock.POSIX
|
import Data.Time.Clock.POSIX
|
||||||
import Data.Time
|
|
||||||
import System.Locale
|
|
||||||
import qualified Data.Map as M
|
|
||||||
|
|
||||||
|
import Logs.Presence.Pure as X
|
||||||
import Common.Annex
|
import Common.Annex
|
||||||
import qualified Annex.Branch
|
import qualified Annex.Branch
|
||||||
import Utility.QuickCheck
|
|
||||||
|
|
||||||
data LogLine = LogLine {
|
|
||||||
date :: POSIXTime,
|
|
||||||
status :: LogStatus,
|
|
||||||
info :: String
|
|
||||||
} deriving (Eq, Show)
|
|
||||||
|
|
||||||
data LogStatus = InfoPresent | InfoMissing
|
|
||||||
deriving (Eq, Show, Bounded, Enum)
|
|
||||||
|
|
||||||
addLog :: FilePath -> LogLine -> Annex ()
|
addLog :: FilePath -> LogLine -> Annex ()
|
||||||
addLog file line = Annex.Branch.change file $ \s ->
|
addLog file line = Annex.Branch.change file $ \s ->
|
||||||
|
@ -52,29 +34,6 @@ addLog file line = Annex.Branch.change file $ \s ->
|
||||||
readLog :: FilePath -> Annex [LogLine]
|
readLog :: FilePath -> Annex [LogLine]
|
||||||
readLog = parseLog <$$> Annex.Branch.get
|
readLog = parseLog <$$> Annex.Branch.get
|
||||||
|
|
||||||
{- Parses a log file. Unparseable lines are ignored. -}
|
|
||||||
parseLog :: String -> [LogLine]
|
|
||||||
parseLog = mapMaybe parseline . lines
|
|
||||||
where
|
|
||||||
parseline l = LogLine
|
|
||||||
<$> (utcTimeToPOSIXSeconds <$> parseTime defaultTimeLocale "%s%Qs" d)
|
|
||||||
<*> parsestatus s
|
|
||||||
<*> pure rest
|
|
||||||
where
|
|
||||||
(d, pastd) = separate (== ' ') l
|
|
||||||
(s, rest) = separate (== ' ') pastd
|
|
||||||
parsestatus "1" = Just InfoPresent
|
|
||||||
parsestatus "0" = Just InfoMissing
|
|
||||||
parsestatus _ = Nothing
|
|
||||||
|
|
||||||
{- Generates a log file. -}
|
|
||||||
showLog :: [LogLine] -> String
|
|
||||||
showLog = unlines . map genline
|
|
||||||
where
|
|
||||||
genline (LogLine d s i) = unwords [show d, genstatus s, i]
|
|
||||||
genstatus InfoPresent = "1"
|
|
||||||
genstatus InfoMissing = "0"
|
|
||||||
|
|
||||||
{- Generates a new LogLine with the current date. -}
|
{- Generates a new LogLine with the current date. -}
|
||||||
logNow :: LogStatus -> String -> Annex LogLine
|
logNow :: LogStatus -> String -> Annex LogLine
|
||||||
logNow s i = do
|
logNow s i = do
|
||||||
|
@ -84,39 +43,3 @@ logNow s i = do
|
||||||
{- Reads a log and returns only the info that is still in effect. -}
|
{- Reads a log and returns only the info that is still in effect. -}
|
||||||
currentLog :: FilePath -> Annex [String]
|
currentLog :: FilePath -> Annex [String]
|
||||||
currentLog file = map info . filterPresent <$> readLog file
|
currentLog file = map info . filterPresent <$> readLog file
|
||||||
|
|
||||||
{- Given a log, returns only the info that is are still in effect. -}
|
|
||||||
getLog :: String -> [String]
|
|
||||||
getLog = map info . filterPresent . parseLog
|
|
||||||
|
|
||||||
{- Returns the info from LogLines that are in effect. -}
|
|
||||||
filterPresent :: [LogLine] -> [LogLine]
|
|
||||||
filterPresent = filter (\l -> InfoPresent == status l) . compactLog
|
|
||||||
|
|
||||||
{- Compacts a set of logs, returning a subset that contains the current
|
|
||||||
- status. -}
|
|
||||||
compactLog :: [LogLine] -> [LogLine]
|
|
||||||
compactLog = M.elems . foldr mapLog M.empty
|
|
||||||
|
|
||||||
type LogMap = M.Map String LogLine
|
|
||||||
|
|
||||||
{- Inserts a log into a map of logs, if the log has better (ie, newer)
|
|
||||||
- information than the other logs in the map -}
|
|
||||||
mapLog :: LogLine -> LogMap -> LogMap
|
|
||||||
mapLog l m
|
|
||||||
| better = M.insert i l m
|
|
||||||
| otherwise = m
|
|
||||||
where
|
|
||||||
better = maybe True newer $ M.lookup i m
|
|
||||||
newer l' = date l' <= date l
|
|
||||||
i = info l
|
|
||||||
|
|
||||||
instance Arbitrary LogLine where
|
|
||||||
arbitrary = LogLine
|
|
||||||
<$> arbitrary
|
|
||||||
<*> elements [minBound..maxBound]
|
|
||||||
<*> arbitrary `suchThat` ('\n' `notElem`)
|
|
||||||
|
|
||||||
prop_parse_show_log :: [LogLine] -> Bool
|
|
||||||
prop_parse_show_log l = parseLog (showLog l) == l
|
|
||||||
|
|
||||||
|
|
84
Logs/Presence/Pure.hs
Normal file
84
Logs/Presence/Pure.hs
Normal file
|
@ -0,0 +1,84 @@
|
||||||
|
{- git-annex presence log, pure operations
|
||||||
|
-
|
||||||
|
- Copyright 2010-2013 Joey Hess <joey@kitenet.net>
|
||||||
|
-
|
||||||
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
|
-}
|
||||||
|
|
||||||
|
module Logs.Presence.Pure where
|
||||||
|
|
||||||
|
import Data.Time.Clock.POSIX
|
||||||
|
import Data.Time
|
||||||
|
import System.Locale
|
||||||
|
import qualified Data.Map as M
|
||||||
|
|
||||||
|
import Common.Annex
|
||||||
|
import Utility.QuickCheck
|
||||||
|
|
||||||
|
data LogLine = LogLine {
|
||||||
|
date :: POSIXTime,
|
||||||
|
status :: LogStatus,
|
||||||
|
info :: String
|
||||||
|
} deriving (Eq, Show)
|
||||||
|
|
||||||
|
data LogStatus = InfoPresent | InfoMissing
|
||||||
|
deriving (Eq, Show, Bounded, Enum)
|
||||||
|
|
||||||
|
{- Parses a log file. Unparseable lines are ignored. -}
|
||||||
|
parseLog :: String -> [LogLine]
|
||||||
|
parseLog = mapMaybe parseline . lines
|
||||||
|
where
|
||||||
|
parseline l = LogLine
|
||||||
|
<$> (utcTimeToPOSIXSeconds <$> parseTime defaultTimeLocale "%s%Qs" d)
|
||||||
|
<*> parsestatus s
|
||||||
|
<*> pure rest
|
||||||
|
where
|
||||||
|
(d, pastd) = separate (== ' ') l
|
||||||
|
(s, rest) = separate (== ' ') pastd
|
||||||
|
parsestatus "1" = Just InfoPresent
|
||||||
|
parsestatus "0" = Just InfoMissing
|
||||||
|
parsestatus _ = Nothing
|
||||||
|
|
||||||
|
{- Generates a log file. -}
|
||||||
|
showLog :: [LogLine] -> String
|
||||||
|
showLog = unlines . map genline
|
||||||
|
where
|
||||||
|
genline (LogLine d s i) = unwords [show d, genstatus s, i]
|
||||||
|
genstatus InfoPresent = "1"
|
||||||
|
genstatus InfoMissing = "0"
|
||||||
|
|
||||||
|
{- Given a log, returns only the info that is are still in effect. -}
|
||||||
|
getLog :: String -> [String]
|
||||||
|
getLog = map info . filterPresent . parseLog
|
||||||
|
|
||||||
|
{- Returns the info from LogLines that are in effect. -}
|
||||||
|
filterPresent :: [LogLine] -> [LogLine]
|
||||||
|
filterPresent = filter (\l -> InfoPresent == status l) . compactLog
|
||||||
|
|
||||||
|
{- Compacts a set of logs, returning a subset that contains the current
|
||||||
|
- status. -}
|
||||||
|
compactLog :: [LogLine] -> [LogLine]
|
||||||
|
compactLog = M.elems . foldr mapLog M.empty
|
||||||
|
|
||||||
|
type LogMap = M.Map String LogLine
|
||||||
|
|
||||||
|
{- Inserts a log into a map of logs, if the log has better (ie, newer)
|
||||||
|
- information than the other logs in the map -}
|
||||||
|
mapLog :: LogLine -> LogMap -> LogMap
|
||||||
|
mapLog l m
|
||||||
|
| better = M.insert i l m
|
||||||
|
| otherwise = m
|
||||||
|
where
|
||||||
|
better = maybe True newer $ M.lookup i m
|
||||||
|
newer l' = date l' <= date l
|
||||||
|
i = info l
|
||||||
|
|
||||||
|
instance Arbitrary LogLine where
|
||||||
|
arbitrary = LogLine
|
||||||
|
<$> arbitrary
|
||||||
|
<*> elements [minBound..maxBound]
|
||||||
|
<*> arbitrary `suchThat` ('\n' `notElem`)
|
||||||
|
|
||||||
|
prop_parse_show_log :: [LogLine] -> Bool
|
||||||
|
prop_parse_show_log l = parseLog (showLog l) == l
|
||||||
|
|
|
@ -25,12 +25,9 @@ import Data.Char
|
||||||
import Common.Annex
|
import Common.Annex
|
||||||
import qualified Annex.Branch
|
import qualified Annex.Branch
|
||||||
import Types.Remote
|
import Types.Remote
|
||||||
|
import Logs
|
||||||
import Logs.UUIDBased
|
import Logs.UUIDBased
|
||||||
|
|
||||||
{- Filename of remote.log. -}
|
|
||||||
remoteLog :: FilePath
|
|
||||||
remoteLog = "remote.log"
|
|
||||||
|
|
||||||
{- Adds or updates a remote's config in the log. -}
|
{- Adds or updates a remote's config in the log. -}
|
||||||
configSet :: UUID -> RemoteConfig -> Annex ()
|
configSet :: UUID -> RemoteConfig -> Annex ()
|
||||||
configSet u c = do
|
configSet u c = do
|
||||||
|
|
87
Logs/Transitions.hs
Normal file
87
Logs/Transitions.hs
Normal file
|
@ -0,0 +1,87 @@
|
||||||
|
{- git-annex transitions log
|
||||||
|
-
|
||||||
|
- This is used to record transitions that have been performed on the
|
||||||
|
- git-annex branch, and when the transition was first started.
|
||||||
|
-
|
||||||
|
- We can quickly detect when the local branch has already had an transition
|
||||||
|
- done that is listed in the remote branch by checking that the local
|
||||||
|
- branch contains the same transition, with the same or newer start time.
|
||||||
|
-
|
||||||
|
- Copyright 2013 Joey Hess <joey@kitenet.net>
|
||||||
|
-
|
||||||
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
|
-}
|
||||||
|
|
||||||
|
module Logs.Transitions where
|
||||||
|
|
||||||
|
import Data.Time.Clock.POSIX
|
||||||
|
import Data.Time
|
||||||
|
import System.Locale
|
||||||
|
import qualified Data.Set as S
|
||||||
|
|
||||||
|
import Common.Annex
|
||||||
|
|
||||||
|
transitionsLog :: FilePath
|
||||||
|
transitionsLog = "transitions.log"
|
||||||
|
|
||||||
|
data Transition
|
||||||
|
= ForgetGitHistory
|
||||||
|
| ForgetDeadRemotes
|
||||||
|
deriving (Show, Ord, Eq, Read)
|
||||||
|
|
||||||
|
data TransitionLine = TransitionLine
|
||||||
|
{ transitionStarted :: POSIXTime
|
||||||
|
, transition :: Transition
|
||||||
|
} deriving (Show, Ord, Eq)
|
||||||
|
|
||||||
|
type Transitions = S.Set TransitionLine
|
||||||
|
|
||||||
|
describeTransition :: Transition -> String
|
||||||
|
describeTransition ForgetGitHistory = "forget git history"
|
||||||
|
describeTransition ForgetDeadRemotes = "forget dead remotes"
|
||||||
|
|
||||||
|
noTransitions :: Transitions
|
||||||
|
noTransitions = S.empty
|
||||||
|
|
||||||
|
addTransition :: POSIXTime -> Transition -> Transitions -> Transitions
|
||||||
|
addTransition ts t = S.insert $ TransitionLine ts t
|
||||||
|
|
||||||
|
showTransitions :: Transitions -> String
|
||||||
|
showTransitions = unlines . map showTransitionLine . S.elems
|
||||||
|
|
||||||
|
{- If the log contains new transitions we don't support, returns Nothing. -}
|
||||||
|
parseTransitions :: String -> Maybe Transitions
|
||||||
|
parseTransitions = check . map parseTransitionLine . lines
|
||||||
|
where
|
||||||
|
check l
|
||||||
|
| all isJust l = Just $ S.fromList $ catMaybes l
|
||||||
|
| otherwise = Nothing
|
||||||
|
|
||||||
|
parseTransitionsStrictly :: String -> String -> Transitions
|
||||||
|
parseTransitionsStrictly source = fromMaybe badsource . parseTransitions
|
||||||
|
where
|
||||||
|
badsource = error $ "unknown transitions listed in " ++ source ++ "; upgrade git-annex!"
|
||||||
|
|
||||||
|
showTransitionLine :: TransitionLine -> String
|
||||||
|
showTransitionLine (TransitionLine ts t) = unwords [show t, show ts]
|
||||||
|
|
||||||
|
parseTransitionLine :: String -> Maybe TransitionLine
|
||||||
|
parseTransitionLine s = TransitionLine <$> pdate ds <*> readish ts
|
||||||
|
where
|
||||||
|
ws = words s
|
||||||
|
ts = Prelude.head ws
|
||||||
|
ds = unwords $ Prelude.tail ws
|
||||||
|
pdate = parseTime defaultTimeLocale "%s%Qs" >=*> utcTimeToPOSIXSeconds
|
||||||
|
|
||||||
|
combineTransitions :: [Transitions] -> Transitions
|
||||||
|
combineTransitions = S.unions
|
||||||
|
|
||||||
|
transitionList :: Transitions -> [Transition]
|
||||||
|
transitionList = map transition . S.elems
|
||||||
|
|
||||||
|
{- Typically ran with Annex.Branch.change, but we can't import Annex.Branch
|
||||||
|
- here since it depends on this module. -}
|
||||||
|
recordTransitions :: (FilePath -> (String -> String) -> Annex ()) -> Transitions -> Annex ()
|
||||||
|
recordTransitions changer t = do
|
||||||
|
changer transitionsLog $
|
||||||
|
showTransitions . S.union t . parseTransitionsStrictly "local"
|
|
@ -6,6 +6,7 @@
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Logs.Trust (
|
module Logs.Trust (
|
||||||
|
module X,
|
||||||
trustLog,
|
trustLog,
|
||||||
TrustLevel(..),
|
TrustLevel(..),
|
||||||
trustGet,
|
trustGet,
|
||||||
|
@ -16,8 +17,6 @@ module Logs.Trust (
|
||||||
lookupTrust,
|
lookupTrust,
|
||||||
trustMapLoad,
|
trustMapLoad,
|
||||||
trustMapRaw,
|
trustMapRaw,
|
||||||
|
|
||||||
prop_parse_show_TrustLog,
|
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
|
@ -27,13 +26,11 @@ import Common.Annex
|
||||||
import Types.TrustLevel
|
import Types.TrustLevel
|
||||||
import qualified Annex.Branch
|
import qualified Annex.Branch
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
|
import Logs
|
||||||
import Logs.UUIDBased
|
import Logs.UUIDBased
|
||||||
import Remote.List
|
import Remote.List
|
||||||
import qualified Types.Remote
|
import qualified Types.Remote
|
||||||
|
import Logs.Trust.Pure as X
|
||||||
{- Filename of trust.log. -}
|
|
||||||
trustLog :: FilePath
|
|
||||||
trustLog = "trust.log"
|
|
||||||
|
|
||||||
{- Returns a list of UUIDs that the trustLog indicates have the
|
{- Returns a list of UUIDs that the trustLog indicates have the
|
||||||
- specified trust level.
|
- specified trust level.
|
||||||
|
@ -97,26 +94,4 @@ trustMapLoad = do
|
||||||
{- Does not include forcetrust or git config values, just those from the
|
{- Does not include forcetrust or git config values, just those from the
|
||||||
- log file. -}
|
- log file. -}
|
||||||
trustMapRaw :: Annex TrustMap
|
trustMapRaw :: Annex TrustMap
|
||||||
trustMapRaw = simpleMap . parseLog (Just . parseTrustLog)
|
trustMapRaw = calcTrustMap <$> Annex.Branch.get trustLog
|
||||||
<$> Annex.Branch.get trustLog
|
|
||||||
|
|
||||||
{- The trust.log used to only list trusted repos, without a field for the
|
|
||||||
- trust status, which is why this defaults to Trusted. -}
|
|
||||||
parseTrustLog :: String -> TrustLevel
|
|
||||||
parseTrustLog s = maybe Trusted parse $ headMaybe $ words s
|
|
||||||
where
|
|
||||||
parse "1" = Trusted
|
|
||||||
parse "0" = UnTrusted
|
|
||||||
parse "X" = DeadTrusted
|
|
||||||
parse _ = SemiTrusted
|
|
||||||
|
|
||||||
showTrustLog :: TrustLevel -> String
|
|
||||||
showTrustLog Trusted = "1"
|
|
||||||
showTrustLog UnTrusted = "0"
|
|
||||||
showTrustLog DeadTrusted = "X"
|
|
||||||
showTrustLog SemiTrusted = "?"
|
|
||||||
|
|
||||||
prop_parse_show_TrustLog :: Bool
|
|
||||||
prop_parse_show_TrustLog = all check [minBound .. maxBound]
|
|
||||||
where
|
|
||||||
check l = parseTrustLog (showTrustLog l) == l
|
|
||||||
|
|
36
Logs/Trust/Pure.hs
Normal file
36
Logs/Trust/Pure.hs
Normal file
|
@ -0,0 +1,36 @@
|
||||||
|
{- git-annex trust log, pure operations
|
||||||
|
-
|
||||||
|
- Copyright 2010-2013 Joey Hess <joey@kitenet.net>
|
||||||
|
-
|
||||||
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
|
-}
|
||||||
|
|
||||||
|
module Logs.Trust.Pure where
|
||||||
|
|
||||||
|
import Common.Annex
|
||||||
|
import Types.TrustLevel
|
||||||
|
import Logs.UUIDBased
|
||||||
|
|
||||||
|
calcTrustMap :: String -> TrustMap
|
||||||
|
calcTrustMap = simpleMap . parseLog (Just . parseTrustLog)
|
||||||
|
|
||||||
|
{- The trust.log used to only list trusted repos, without a field for the
|
||||||
|
- trust status, which is why this defaults to Trusted. -}
|
||||||
|
parseTrustLog :: String -> TrustLevel
|
||||||
|
parseTrustLog s = maybe Trusted parse $ headMaybe $ words s
|
||||||
|
where
|
||||||
|
parse "1" = Trusted
|
||||||
|
parse "0" = UnTrusted
|
||||||
|
parse "X" = DeadTrusted
|
||||||
|
parse _ = SemiTrusted
|
||||||
|
|
||||||
|
showTrustLog :: TrustLevel -> String
|
||||||
|
showTrustLog Trusted = "1"
|
||||||
|
showTrustLog UnTrusted = "0"
|
||||||
|
showTrustLog DeadTrusted = "X"
|
||||||
|
showTrustLog SemiTrusted = "?"
|
||||||
|
|
||||||
|
prop_parse_show_TrustLog :: Bool
|
||||||
|
prop_parse_show_TrustLog = all check [minBound .. maxBound]
|
||||||
|
where
|
||||||
|
check l = parseTrustLog (showTrustLog l) == l
|
|
@ -28,13 +28,10 @@ import Types.UUID
|
||||||
import Common.Annex
|
import Common.Annex
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import qualified Annex.Branch
|
import qualified Annex.Branch
|
||||||
|
import Logs
|
||||||
import Logs.UUIDBased
|
import Logs.UUIDBased
|
||||||
import qualified Annex.UUID
|
import qualified Annex.UUID
|
||||||
|
|
||||||
{- Filename of uuid.log. -}
|
|
||||||
uuidLog :: FilePath
|
|
||||||
uuidLog = "uuid.log"
|
|
||||||
|
|
||||||
{- Records a description for a uuid in the log. -}
|
{- Records a description for a uuid in the log. -}
|
||||||
describeUUID :: UUID -> String -> Annex ()
|
describeUUID :: UUID -> String -> Annex ()
|
||||||
describeUUID uuid desc = do
|
describeUUID uuid desc = do
|
||||||
|
|
36
Logs/Web.hs
36
Logs/Web.hs
|
@ -11,8 +11,6 @@ module Logs.Web (
|
||||||
getUrls,
|
getUrls,
|
||||||
setUrlPresent,
|
setUrlPresent,
|
||||||
setUrlMissing,
|
setUrlMissing,
|
||||||
urlLog,
|
|
||||||
urlLogKey,
|
|
||||||
knownUrls,
|
knownUrls,
|
||||||
Downloader(..),
|
Downloader(..),
|
||||||
getDownloader,
|
getDownloader,
|
||||||
|
@ -22,9 +20,9 @@ module Logs.Web (
|
||||||
import qualified Data.ByteString.Lazy.Char8 as L
|
import qualified Data.ByteString.Lazy.Char8 as L
|
||||||
|
|
||||||
import Common.Annex
|
import Common.Annex
|
||||||
|
import Logs
|
||||||
import Logs.Presence
|
import Logs.Presence
|
||||||
import Logs.Location
|
import Logs.Location
|
||||||
import Types.Key
|
|
||||||
import qualified Annex.Branch
|
import qualified Annex.Branch
|
||||||
import Annex.CatFile
|
import Annex.CatFile
|
||||||
import qualified Git
|
import qualified Git
|
||||||
|
@ -36,35 +34,9 @@ type URLString = String
|
||||||
webUUID :: UUID
|
webUUID :: UUID
|
||||||
webUUID = UUID "00000000-0000-0000-0000-000000000001"
|
webUUID = UUID "00000000-0000-0000-0000-000000000001"
|
||||||
|
|
||||||
urlLogExt :: String
|
|
||||||
urlLogExt = ".log.web"
|
|
||||||
|
|
||||||
urlLog :: Key -> FilePath
|
|
||||||
urlLog key = hashDirLower key </> keyFile key ++ urlLogExt
|
|
||||||
|
|
||||||
{- Converts a url log file into a key.
|
|
||||||
- (Does not work on oldurlLogs.) -}
|
|
||||||
urlLogKey :: FilePath -> Maybe Key
|
|
||||||
urlLogKey file
|
|
||||||
| ext == urlLogExt = fileKey base
|
|
||||||
| otherwise = Nothing
|
|
||||||
where
|
|
||||||
(base, ext) = splitAt (length file - extlen) file
|
|
||||||
extlen = length urlLogExt
|
|
||||||
|
|
||||||
isUrlLog :: FilePath -> Bool
|
|
||||||
isUrlLog file = urlLogExt `isSuffixOf` file
|
|
||||||
|
|
||||||
{- Used to store the urls elsewhere. -}
|
|
||||||
oldurlLogs :: Key -> [FilePath]
|
|
||||||
oldurlLogs key =
|
|
||||||
[ "remote/web" </> hashDirLower key </> key2file key ++ ".log"
|
|
||||||
, "remote/web" </> hashDirLower key </> keyFile key ++ ".log"
|
|
||||||
]
|
|
||||||
|
|
||||||
{- Gets all urls that a key might be available from. -}
|
{- Gets all urls that a key might be available from. -}
|
||||||
getUrls :: Key -> Annex [URLString]
|
getUrls :: Key -> Annex [URLString]
|
||||||
getUrls key = go $ urlLog key : oldurlLogs key
|
getUrls key = go $ urlLogFile key : oldurlLogs key
|
||||||
where
|
where
|
||||||
go [] = return []
|
go [] = return []
|
||||||
go (l:ls) = do
|
go (l:ls) = do
|
||||||
|
@ -77,13 +49,13 @@ setUrlPresent :: Key -> URLString -> Annex ()
|
||||||
setUrlPresent key url = do
|
setUrlPresent key url = do
|
||||||
us <- getUrls key
|
us <- getUrls key
|
||||||
unless (url `elem` us) $ do
|
unless (url `elem` us) $ do
|
||||||
addLog (urlLog key) =<< logNow InfoPresent url
|
addLog (urlLogFile key) =<< logNow InfoPresent url
|
||||||
-- update location log to indicate that the web has the key
|
-- update location log to indicate that the web has the key
|
||||||
logChange key webUUID InfoPresent
|
logChange key webUUID InfoPresent
|
||||||
|
|
||||||
setUrlMissing :: Key -> URLString -> Annex ()
|
setUrlMissing :: Key -> URLString -> Annex ()
|
||||||
setUrlMissing key url = do
|
setUrlMissing key url = do
|
||||||
addLog (urlLog key) =<< logNow InfoMissing url
|
addLog (urlLogFile key) =<< logNow InfoMissing url
|
||||||
whenM (null <$> getUrls key) $
|
whenM (null <$> getUrls key) $
|
||||||
logChange key webUUID InfoMissing
|
logChange key webUUID InfoMissing
|
||||||
|
|
||||||
|
|
2
Test.hs
2
Test.hs
|
@ -34,6 +34,7 @@ import qualified Types.KeySource
|
||||||
import qualified Types.Backend
|
import qualified Types.Backend
|
||||||
import qualified Types.TrustLevel
|
import qualified Types.TrustLevel
|
||||||
import qualified Types
|
import qualified Types
|
||||||
|
import qualified Logs
|
||||||
import qualified Logs.UUIDBased
|
import qualified Logs.UUIDBased
|
||||||
import qualified Logs.Trust
|
import qualified Logs.Trust
|
||||||
import qualified Logs.Remote
|
import qualified Logs.Remote
|
||||||
|
@ -117,6 +118,7 @@ quickcheck =
|
||||||
, check "prop_idempotent_key_encode" Types.Key.prop_idempotent_key_encode
|
, check "prop_idempotent_key_encode" Types.Key.prop_idempotent_key_encode
|
||||||
, check "prop_idempotent_shellEscape" Utility.SafeCommand.prop_idempotent_shellEscape
|
, check "prop_idempotent_shellEscape" Utility.SafeCommand.prop_idempotent_shellEscape
|
||||||
, check "prop_idempotent_shellEscape_multiword" Utility.SafeCommand.prop_idempotent_shellEscape_multiword
|
, check "prop_idempotent_shellEscape_multiword" Utility.SafeCommand.prop_idempotent_shellEscape_multiword
|
||||||
|
, check "prop_logs_sane" Logs.prop_logs_sane
|
||||||
, check "prop_idempotent_configEscape" Logs.Remote.prop_idempotent_configEscape
|
, check "prop_idempotent_configEscape" Logs.Remote.prop_idempotent_configEscape
|
||||||
, check "prop_parse_show_Config" Logs.Remote.prop_parse_show_Config
|
, check "prop_parse_show_Config" Logs.Remote.prop_parse_show_Config
|
||||||
, check "prop_parentDir_basics" Utility.Path.prop_parentDir_basics
|
, check "prop_parentDir_basics" Utility.Path.prop_parentDir_basics
|
||||||
|
|
|
@ -12,9 +12,9 @@ import qualified Git
|
||||||
import qualified Git.Command
|
import qualified Git.Command
|
||||||
import qualified Git.Ref
|
import qualified Git.Ref
|
||||||
import qualified Annex.Branch
|
import qualified Annex.Branch
|
||||||
import Logs.Location
|
|
||||||
import Annex.Content
|
import Annex.Content
|
||||||
import Utility.Tmp
|
import Utility.Tmp
|
||||||
|
import Logs
|
||||||
|
|
||||||
olddir :: Git.Repo -> FilePath
|
olddir :: Git.Repo -> FilePath
|
||||||
olddir g
|
olddir g
|
||||||
|
@ -47,7 +47,7 @@ upgrade = do
|
||||||
|
|
||||||
e <- liftIO $ doesDirectoryExist old
|
e <- liftIO $ doesDirectoryExist old
|
||||||
when e $ do
|
when e $ do
|
||||||
mapM_ (\(k, f) -> inject f $ logFile k) =<< locationLogs
|
mapM_ (\(k, f) -> inject f $ locationLogFile k) =<< locationLogs
|
||||||
mapM_ (\f -> inject f f) =<< logFiles old
|
mapM_ (\f -> inject f f) =<< logFiles old
|
||||||
|
|
||||||
saveState False
|
saveState False
|
||||||
|
@ -73,7 +73,7 @@ locationLogs = do
|
||||||
where
|
where
|
||||||
tryDirContents d = catchDefaultIO [] $ dirContents d
|
tryDirContents d = catchDefaultIO [] $ dirContents d
|
||||||
islogfile f = maybe Nothing (\k -> Just (k, f)) $
|
islogfile f = maybe Nothing (\k -> Just (k, f)) $
|
||||||
logFileKey $ takeFileName f
|
locationLogFileKey f
|
||||||
|
|
||||||
inject :: FilePath -> FilePath -> Annex ()
|
inject :: FilePath -> FilePath -> Annex ()
|
||||||
inject source dest = do
|
inject source dest = do
|
||||||
|
|
|
@ -91,6 +91,12 @@ massReplace vs = go [] vs
|
||||||
go (replacement:acc) vs (drop (length val) s)
|
go (replacement:acc) vs (drop (length val) s)
|
||||||
| otherwise = go acc rest s
|
| otherwise = go acc rest s
|
||||||
|
|
||||||
|
{- First item in the list that is not Nothing. -}
|
||||||
|
firstJust :: Eq a => [Maybe a] -> Maybe a
|
||||||
|
firstJust ms = case dropWhile (== Nothing) ms of
|
||||||
|
[] -> Nothing
|
||||||
|
(md:_) -> md
|
||||||
|
|
||||||
{- Given two orderings, returns the second if the first is EQ and returns
|
{- Given two orderings, returns the second if the first is EQ and returns
|
||||||
- the first otherwise.
|
- the first otherwise.
|
||||||
-
|
-
|
||||||
|
|
14
debian/changelog
vendored
14
debian/changelog
vendored
|
@ -1,3 +1,17 @@
|
||||||
|
git-annex (4.20130828) UNRELEASED; urgency=low
|
||||||
|
|
||||||
|
* forget: New command, causes git-annex branch history to be forgotten
|
||||||
|
in a way that will spread to other clones of the repository.
|
||||||
|
(As long as they're running this version or newer of git-annex.)
|
||||||
|
* forget --drop-dead: Completely removes mentions of repositories that
|
||||||
|
have been marked as dead from the git-annex branch.
|
||||||
|
* sync, assistant: Force push of the git-annex branch. Necessary
|
||||||
|
to ensure it gets pushed to remotes after being rewritten by forget.
|
||||||
|
* importfeed: Also ignore transient problems with downloading content
|
||||||
|
from feeds.
|
||||||
|
* Honor core.sharedrepository when receiving and adding files in direct
|
||||||
|
mode.
|
||||||
|
|
||||||
git-annex (4.20130827) unstable; urgency=low
|
git-annex (4.20130827) unstable; urgency=low
|
||||||
|
|
||||||
* Youtube support! (And 53 other video hosts). When quvi is installed,
|
* Youtube support! (And 53 other video hosts). When quvi is installed,
|
||||||
|
|
|
@ -15,3 +15,11 @@ files transit through a special remote, using modes to limit access to
|
||||||
individual files is not wise.)
|
individual files is not wise.)
|
||||||
|
|
||||||
--[[Joey]]
|
--[[Joey]]
|
||||||
|
|
||||||
|
> Revisiting this, git-annex already honors core.sharedrepository settings,
|
||||||
|
> so I just needed to set it to `world` to allow everyone to read.
|
||||||
|
>
|
||||||
|
> There was a code path in direct mode where that didn't work; fixed that.
|
||||||
|
>
|
||||||
|
> [[done]]
|
||||||
|
> --[[Joey]]
|
||||||
|
|
|
@ -0,0 +1,22 @@
|
||||||
|
### Please describe the problem.
|
||||||
|
When I try to add a box.com cloud repository with the encryption option selected, I get an error that says "internal server error".
|
||||||
|
|
||||||
|
### What steps will reproduce the problem?
|
||||||
|
Anytime I try to set up a cloud repository with box.com (and presumably others, since this seems to be a problem with gpg (see log)) that is encrypted, I get this error.
|
||||||
|
|
||||||
|
|
||||||
|
### What version of git-annex are you using? On what operating system?
|
||||||
|
The operating system is Mac OS X 10.8.4, and the version of git-annex is 4.20130801-gc88bbc4.
|
||||||
|
|
||||||
|
|
||||||
|
### Please provide any additional information below.
|
||||||
|
|
||||||
|
[[!format sh """
|
||||||
|
# If you can, paste a complete transcript of the problem occurring here.
|
||||||
|
# If the problem is with the git-annex assistant, paste in .git/annex/daemon.log
|
||||||
|
|
||||||
|
(encryption setup) gpg: /Users/adamliter/.gnupg/gpg.conf:233: invalid auto-key-locate list
|
||||||
|
30/Aug/2013:02:27:11 -0400 [Error#yesod-core] user error (gpg ["--quiet","--trust-model","always","--gen-random","--armor","1","512"] exited 2) @(yesod-core-1.1.8.3:Yesod.Internal.Core ./Yesod/Internal/Core.hs:550:5)
|
||||||
|
|
||||||
|
# End of transcript or log.
|
||||||
|
"""]]
|
|
@ -0,0 +1,10 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="guilhem"
|
||||||
|
ip="129.16.20.209"
|
||||||
|
subject="comment 1"
|
||||||
|
date="2013-08-30T11:39:51Z"
|
||||||
|
content="""
|
||||||
|
gpg complains about an invalid parameter for the `auto-key-locate` option, which is not passed by git-annex but found in your gpg.conf.
|
||||||
|
|
||||||
|
What is on line 233 of `/Users/adamliter/.gnupg/gpg.conf`?
|
||||||
|
"""]]
|
|
@ -0,0 +1,8 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="https://www.google.com/accounts/o8/id?id=AItOawkgH7oNEqNbh3g-N1-UHXuqleXaRYDgj1U"
|
||||||
|
nickname="Adam"
|
||||||
|
subject="comment 2"
|
||||||
|
date="2013-08-30T15:39:16Z"
|
||||||
|
content="""
|
||||||
|
\"auto-key-locate cert pka ldap hkp://keys.gnupg.net\" is on line 233
|
||||||
|
"""]]
|
|
@ -0,0 +1,16 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="guilhem"
|
||||||
|
ip="129.16.20.209"
|
||||||
|
subject="comment 3"
|
||||||
|
date="2013-08-30T16:09:58Z"
|
||||||
|
content="""
|
||||||
|
Hmm, it looks like a perfectly valid list. Interesting.
|
||||||
|
But regardless, gpg doesn't seem to like that line; what gpg version
|
||||||
|
are you using? Also, does it work directly on the command-line
|
||||||
|
(`gpg -a --gen-random 1 1`)?
|
||||||
|
|
||||||
|
Have you tried to setup the remote without that line in the gpg.conf? Of
|
||||||
|
course it wouldn't solve the core of the issue, but it's irrelevant for
|
||||||
|
random data generation anyway (the same goes for `--trust-model`);
|
||||||
|
perhaps this very command should be run with `--no-options`.
|
||||||
|
"""]]
|
|
@ -0,0 +1,12 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="https://www.google.com/accounts/o8/id?id=AItOawkgH7oNEqNbh3g-N1-UHXuqleXaRYDgj1U"
|
||||||
|
nickname="Adam"
|
||||||
|
subject="comment 4"
|
||||||
|
date="2013-08-30T21:39:26Z"
|
||||||
|
content="""
|
||||||
|
`gpg -a --gen-random 1 1` on the command line seems to work. At least, when I just ran it it returned `Xg==`. I'm not super familiar with running gpg on the command line, so I'm not sure if that is the desired result when running that.
|
||||||
|
|
||||||
|
The version of gpg is GnuPG/MacGPG2 version 2.0.20.
|
||||||
|
|
||||||
|
I just tried deleting that line from the config file, and now it worked. Would I be able to replace the line after setting up the repository, or is that going to create problems? I'm not entirely sure what that line does, and I'm a little wary about messing with it in case it breaks the functionality of any of the other things that I use gpg for, like email encryption.
|
||||||
|
"""]]
|
|
@ -0,0 +1,13 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="guilhem"
|
||||||
|
ip="129.16.20.209"
|
||||||
|
subject="comment 5"
|
||||||
|
date="2013-08-30T22:51:56Z"
|
||||||
|
content="""
|
||||||
|
OK (you just generated 1 byte of base64-encoded random data).
|
||||||
|
No, I'm afraid git-annex will croak for each operation using gpg on your remote (which includes get, push, fsck, ...).
|
||||||
|
|
||||||
|
This lines specifies how gpg automatically retrieves public keys when you get a signed message for instance. If you don't want to mix configurations, it is easy to create a git-annex-specific GnuPG home directory, but it requires you to point the `GNUPGHOME` to this alternative directory before starting git-annex.
|
||||||
|
|
||||||
|
That said, other MacOSX users have encountered the same problem, and it was [[reported_to_be_solved_recently|/bugs/internal_server_error_when_choosing_encrypted_rsync_repo_option/]].
|
||||||
|
"""]]
|
|
@ -0,0 +1,10 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="https://me.yahoo.com/a/2grhJvAC049fJnvALDXek.6MRZMTlg--#eec89"
|
||||||
|
nickname="John"
|
||||||
|
subject="comment 9"
|
||||||
|
date="2013-08-30T05:59:28Z"
|
||||||
|
content="""
|
||||||
|
I'll chime in and say that the non-fast behavior being the default seems wrong, and making hard-link invisibly seems wrong. What Joey proposed -- copying a file if there are multiple hard-links -- seems like the right solution.
|
||||||
|
|
||||||
|
Just recently I tried to unannex a large repository and was bitten by now-dangling symlinks to files that I couldn't locate anymore. The fact is that the current unannex operation is too dangerous to be useful.
|
||||||
|
"""]]
|
|
@ -0,0 +1,8 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="https://me.yahoo.com/a/2grhJvAC049fJnvALDXek.6MRZMTlg--#eec89"
|
||||||
|
nickname="John"
|
||||||
|
subject="comment 6"
|
||||||
|
date="2013-08-30T04:19:57Z"
|
||||||
|
content="""
|
||||||
|
Just saw it happen again today, in a repository that passed \"fsck -A\" multiple times just yesterday. What is going on?
|
||||||
|
"""]]
|
|
@ -0,0 +1,14 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="https://me.yahoo.com/a/2grhJvAC049fJnvALDXek.6MRZMTlg--#eec89"
|
||||||
|
nickname="John"
|
||||||
|
subject="comment 7"
|
||||||
|
date="2013-08-30T04:25:45Z"
|
||||||
|
content="""
|
||||||
|
I tried your suggestion of cloning the repository and moving `.git/config` and `.git/annex`, and got this:
|
||||||
|
|
||||||
|
fsck Astronomy/12_ATM_2.jpg error: invalid object 100644 06f8fe222f052100101e5c2e77640f2ec3efff98 for '002/0a6/SHA256E-s427690--03aeabcde841b66168b72de80098d74e047f3ffc832d4bbefa1f2f70ee6c92f8.jpg.log'
|
||||||
|
fatal: git-write-tree: error building trees
|
||||||
|
git-annex: failed to read sha from git write-tree
|
||||||
|
|
||||||
|
What else can I try? Note that I can't even find this `.log` anywhere under my `.git` directory for this repository.
|
||||||
|
"""]]
|
|
@ -0,0 +1,8 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="https://me.yahoo.com/a/2grhJvAC049fJnvALDXek.6MRZMTlg--#eec89"
|
||||||
|
nickname="John"
|
||||||
|
subject="comment 8"
|
||||||
|
date="2013-08-30T04:30:14Z"
|
||||||
|
content="""
|
||||||
|
The only thing that worked was nuking `.git/annex/index` and letting `git-annex sync` rebuild it.
|
||||||
|
"""]]
|
|
@ -0,0 +1,14 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="https://me.yahoo.com/a/2grhJvAC049fJnvALDXek.6MRZMTlg--#eec89"
|
||||||
|
nickname="John"
|
||||||
|
subject="comment 9"
|
||||||
|
date="2013-08-30T06:20:58Z"
|
||||||
|
content="""
|
||||||
|
And yet again it happens:
|
||||||
|
|
||||||
|
error: invalid object 100644 3edb1d4a44ffba1ea1491693ae7d9faa82aad717 for '000/4ce/SHA256E-s175006724--a0edc4f880223028b3fa3a27b142c8e027ddf66db973b8272ca845a4a9e01d3e.mp4.log' fatal: git-write-tree: error building trees
|
||||||
|
|
||||||
|
This was in a repository that was working perfectly well until I tried to `git-annex get`. The weird thing is that I don't even have any `SHA256E` files anymore.
|
||||||
|
|
||||||
|
I think that after my recent migration, none of my repositories can be trusted. This is just happening too often (more than 10 times in the last week, across many repositories on many machines). I will just rebuild them all. But I do wish git-annex was more resilient about this.
|
||||||
|
"""]]
|
|
@ -0,0 +1,68 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="https://www.google.com/accounts/o8/id?id=AItOawknruiCHUcOh2mmpkh7OFJ4iNfAOOamRVs"
|
||||||
|
nickname="Renaud"
|
||||||
|
subject="comment 1"
|
||||||
|
date="2013-08-29T06:38:44Z"
|
||||||
|
content="""
|
||||||
|
I wonder if it isn't related to the fact that even if I do `git annex drop` on windows, the file is still marked as modified in git.
|
||||||
|
What is in repository is the path to the file's data using unix style folder separator but what is in my working directory is a file containing the path using windows style folder separator.
|
||||||
|
|
||||||
|
I paste a transcript to describe what I mean:
|
||||||
|
|
||||||
|
[[!format sh \"\"\"
|
||||||
|
$ mkdir tmp
|
||||||
|
|
||||||
|
$ cd tmp
|
||||||
|
|
||||||
|
$ git init
|
||||||
|
Initialized empty Git repository in c:/Users/raz/tmp/tmp/.git/
|
||||||
|
|
||||||
|
$ git annex init test
|
||||||
|
init test
|
||||||
|
Detected a crippled filesystem.
|
||||||
|
|
||||||
|
Enabling direct mode.
|
||||||
|
|
||||||
|
Detected a filesystem without fifo support.
|
||||||
|
|
||||||
|
Disabling ssh connection caching.
|
||||||
|
ok
|
||||||
|
(Recording state in git...)
|
||||||
|
|
||||||
|
$ echo test > test
|
||||||
|
|
||||||
|
$ git annex add
|
||||||
|
add test (checksum...) ok
|
||||||
|
(Recording state in git...)
|
||||||
|
|
||||||
|
$ git annex sync
|
||||||
|
commit
|
||||||
|
ok
|
||||||
|
git-annex: no branch is checked out
|
||||||
|
|
||||||
|
$ git annex drop --force
|
||||||
|
drop test ok
|
||||||
|
(Recording state in git...)
|
||||||
|
|
||||||
|
$ git status
|
||||||
|
# On branch master
|
||||||
|
# Changes not staged for commit:
|
||||||
|
# (use \"git add <file>...\" to update what will be committed)
|
||||||
|
# (use \"git checkout -- <file>...\" to discard changes in working directory)
|
||||||
|
#
|
||||||
|
# modified: test
|
||||||
|
#
|
||||||
|
no changes added to commit (use \"git add\" and/or \"git commit -a\")
|
||||||
|
|
||||||
|
$ git diff
|
||||||
|
diff --git a/test b/test
|
||||||
|
index a9dd439..62343b2 120000
|
||||||
|
--- a/test
|
||||||
|
+++ b/test
|
||||||
|
@@ -1 +1 @@
|
||||||
|
-.git/annex/objects/w8/pv/SHA256E-s5--f2ca1bb6c7e907d06dafe4687e579fce76b37e4e93
|
||||||
|
\ No newline at end of file
|
||||||
|
+.git\annex\objects\w8\pv\SHA256E-s5--f2ca1bb6c7e907d06dafe4687e579fce76b37e4e93
|
||||||
|
\ No newline at end of file
|
||||||
|
\"\"\"]]
|
||||||
|
"""]]
|
|
@ -0,0 +1,8 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="https://www.google.com/accounts/o8/id?id=AItOawkgedYqmQb4dJU7UdVuRLwsQE-KlKVrFto"
|
||||||
|
nickname="Chungy"
|
||||||
|
subject="comment 3"
|
||||||
|
date="2013-09-01T00:25:15Z"
|
||||||
|
content="""
|
||||||
|
Just confirming the bug on my Verizon Galaxy S 3 with CyanogenMod 10.2 (Android 4.3), it's not Nexus-specific.
|
||||||
|
"""]]
|
|
@ -0,0 +1,8 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="https://www.google.com/accounts/o8/id?id=AItOawntVnR-Z5ghYInvsElbDeADPSuCsF18iTY"
|
||||||
|
nickname="Thomas"
|
||||||
|
subject="comment 4"
|
||||||
|
date="2013-09-01T20:02:59Z"
|
||||||
|
content="""
|
||||||
|
Yet another confirmation of the bug on a Samsung Galaxy Note running 4.3 via Cyanogenmod as well.
|
||||||
|
"""]]
|
|
@ -0,0 +1,9 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="http://edheil.wordpress.com/"
|
||||||
|
ip="173.162.44.162"
|
||||||
|
subject="comment 5"
|
||||||
|
date="2013-09-03T14:38:51Z"
|
||||||
|
content="""
|
||||||
|
If there's anything we can do to help debug this, please let us know. Have just started using git-annex on android recently & would love to have it on all my devices.
|
||||||
|
|
||||||
|
"""]]
|
|
@ -0,0 +1,10 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="http://joeyh.name/"
|
||||||
|
ip="4.153.8.7"
|
||||||
|
subject="comment 2"
|
||||||
|
date="2013-08-29T18:15:08Z"
|
||||||
|
content="""
|
||||||
|
I now have a test case that shows that this can happen reliably on OSX if you enter the wrong XMPP password repeatedly. It might also happen if you just enter the wrong password once, with a server like google's, since the assistant will try falling back to different servers. John is aware of this haskell-gnutls problem.
|
||||||
|
|
||||||
|
John also found, and we hope fixed (but it's hard to tell) a bug in haskell-gnutls that caused a crash maybe 1 time in 10 under some conditions on OSX, when the right password was entered.
|
||||||
|
"""]]
|
|
@ -0,0 +1,8 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="https://www.google.com/accounts/o8/id?id=AItOawlYsjf5dcZnzs0b9EPxnjVddx1rnrpZASs"
|
||||||
|
nickname="Duarte"
|
||||||
|
subject="Any news?"
|
||||||
|
date="2013-08-31T15:48:39Z"
|
||||||
|
content="""
|
||||||
|
Has anyone made any progress on this? Just wondering...
|
||||||
|
"""]]
|
|
@ -0,0 +1,77 @@
|
||||||
|
### Please describe the problem.
|
||||||
|
|
||||||
|
On Mac OS X, I tried to switch a repository to direct mode, but there was a
|
||||||
|
problem in the middle of the switch (permission denied) and the switch
|
||||||
|
aborted, leaving the repository in a half switched state.
|
||||||
|
|
||||||
|
I tried different manipulations, one of which was a checkout (oops), switch
|
||||||
|
back to indirect, then direct again, and now I have the repository in direct
|
||||||
|
mode except one file which caused the permission denied error.
|
||||||
|
|
||||||
|
### What steps will reproduce the problem?
|
||||||
|
|
||||||
|
Do not know exactly why this file is special. I still have the repository, and
|
||||||
|
each time I try to get this file, it fails with the same error message.
|
||||||
|
|
||||||
|
### What version of git-annex are you using? On what operating system?
|
||||||
|
|
||||||
|
On Umba, git-annex version: 4.20130723, on Mac OS X 10.6.8.
|
||||||
|
|
||||||
|
### Please provide any additional information below.
|
||||||
|
|
||||||
|
Umba is the Mac OS X, camaar and riva are Debian machines.
|
||||||
|
|
||||||
|
[[!format sh """
|
||||||
|
Umba$ git annex version
|
||||||
|
git-annex version: 4.20130723
|
||||||
|
build flags: Assistant Webapp Pairing Testsuite S3 WebDAV FsEvents XMPP DNS
|
||||||
|
Umba$
|
||||||
|
|
||||||
|
Umba$ git annex get --from riva --not --in here
|
||||||
|
get 2013-07-31/2013-07-31_180411.jpg (from riva...)
|
||||||
|
Password:
|
||||||
|
SHA256-s2819887--987f9811d7b5c7a287a74b7adbb852be4d18eeda61c3507f4e08c534d2356f4c
|
||||||
|
2819887 100% 943.08kB/s 0:00:02 (xfer#1, to-check=0/1)
|
||||||
|
|
||||||
|
sent 42 bytes received 2820397 bytes 433913.69 bytes/sec
|
||||||
|
total size is 2819887 speedup is 1.00
|
||||||
|
failed
|
||||||
|
git-annex: get: 1 failed
|
||||||
|
Umba$ find . -name SHA256-s2819887-\*
|
||||||
|
./.git/annex/objects/wq/3j/SHA256-s2819887--987f9811d7b5c7a287a74b7adbb852be4d18eeda61c3507f4e08c534d2356f4c
|
||||||
|
./.git/annex/objects/wq/3j/SHA256-s2819887--987f9811d7b5c7a287a74b7adbb852be4d18eeda61c3507f4e08c534d2356f4c/SHA256-s2819887--987f9811d7b5c7a287a74b7adbb852be4d18eeda61c3507f4e08c534d2356f4c.cache
|
||||||
|
./.git/annex/objects/wq/3j/SHA256-s2819887--987f9811d7b5c7a287a74b7adbb852be4d18eeda61c3507f4e08c534d2356f4c/SHA256-s2819887--987f9811d7b5c7a287a74b7adbb852be4d18eeda61c3507f4e08c534d2356f4c.map
|
||||||
|
./.git/annex/transfer/failed/download/13fd5d5a-ed97-11e2-9178-574d3b1c0618/SHA256-s2819887--987f9811d7b5c7a287a74b7adbb852be4d18eeda61c3507f4e08c534d2356f4c
|
||||||
|
./.git/annex/transfer/failed/download/95443f2e-ed96-11e2-9d3f-8ffa5b1aae7a/SHA256-s2819887--987f9811d7b5c7a287a74b7adbb852be4d18eeda61c3507f4e08c534d2356f4c
|
||||||
|
Umba$ git annex fsck
|
||||||
|
fsck 2013-07-31/2013-07-31_180411.jpg ok
|
||||||
|
(Recording state in git...)
|
||||||
|
Umba$ git annex drop 2013-07-31/2013-07-31_180411.jpg
|
||||||
|
Umba$ git annex get --from riva --not --in here
|
||||||
|
get 2013-07-31/2013-07-31_180411.jpg (from riva...)
|
||||||
|
Password:
|
||||||
|
SHA256-s2819887--987f9811d7b5c7a287a74b7adbb852be4d18eeda61c3507f4e08c534d2356f4c
|
||||||
|
2819887 100% 949.58kB/s 0:00:02 (xfer#1, to-check=0/1)
|
||||||
|
|
||||||
|
sent 42 bytes received 2820397 bytes 512807.09 bytes/sec
|
||||||
|
total size is 2819887 speedup is 1.00
|
||||||
|
failed
|
||||||
|
git-annex: get: 1 failed
|
||||||
|
Umba$
|
||||||
|
|
||||||
|
camaar% git annex copy --to umba --not --in umba
|
||||||
|
copy 2013-07-31/2013-07-31_180411.jpg (checking umba...) (to umba...)
|
||||||
|
SHA256-s2819887--987f9811d7b5c7a287a74b7adbb852be4d18eeda61c3507f4e08c534d2356f4c
|
||||||
|
2819887 100% 4.19MB/s 0:00:00 (xfer#1, to-check=0/1)
|
||||||
|
git-annex: //Users/nicolas/Pictures/Petites Boutes/.git/annex/tmp/2013-07-31_18041141700.jpg: rename: permission denied (Operation not permitted)
|
||||||
|
git-annex-shell: recvkey: 1 failed
|
||||||
|
|
||||||
|
sent 2820393 bytes received 42 bytes 1128174.00 bytes/sec
|
||||||
|
total size is 2819887 speedup is 1.00
|
||||||
|
rsync error: syntax or usage error (code 1) at main.c(1070) [sender=3.0.9]
|
||||||
|
|
||||||
|
rsync failed -- run git annex again to resume file transfer
|
||||||
|
failed
|
||||||
|
git-annex: copy: 1 failed
|
||||||
|
camaar%
|
||||||
|
"""]]
|
|
@ -0,0 +1,17 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="http://a-or-b.myopenid.com/"
|
||||||
|
ip="203.45.2.230"
|
||||||
|
subject="comment 1"
|
||||||
|
date="2013-09-04T01:36:46Z"
|
||||||
|
content="""
|
||||||
|
This still is not fixed. :-(
|
||||||
|
|
||||||
|
$ git annex version
|
||||||
|
git-annex version: 4.20130827
|
||||||
|
build flags: Assistant Webapp Pairing Testsuite S3 WebDAV FsEvents XMPP DNS
|
||||||
|
|
||||||
|
|
||||||
|
...but the ```importfeed``` functionality works.
|
||||||
|
|
||||||
|
I know this isn't a particularly high priority bug...
|
||||||
|
"""]]
|
5
doc/devblog/day_-1__drop_dead.mdwn
Normal file
5
doc/devblog/day_-1__drop_dead.mdwn
Normal file
|
@ -0,0 +1,5 @@
|
||||||
|
Implemented `git annex forget --drop-dead`, which is finally a way to
|
||||||
|
remove all references to old repositories that you've marked as dead.
|
||||||
|
|
||||||
|
I've still not merged in the `forget` branch, because I developed this
|
||||||
|
while slightly ill, and have not tested it very well yet.
|
29
doc/devblog/day_-3__.mdwn
Normal file
29
doc/devblog/day_-3__.mdwn
Normal file
|
@ -0,0 +1,29 @@
|
||||||
|
John Millikin came through and fixed that haskell-gnutls segfault
|
||||||
|
on OSX that I developed a reproducible test case for the other day.
|
||||||
|
It's a bit hard to test, since the bug doesn't always happen, but the
|
||||||
|
fix is already deployed for Mountain Lion autobuilder.
|
||||||
|
|
||||||
|
However, I then found another way to make haskell-gnutls segfault, more
|
||||||
|
reliably on OSX, and even sometimes on Linux. Just entering the wrong XMPP
|
||||||
|
password in the assistant can trigger this crash. Hopefully John will work
|
||||||
|
his magic again.
|
||||||
|
|
||||||
|
---
|
||||||
|
|
||||||
|
Meanwhile, I fixed the sync-after-forget problem. Now sync always forces
|
||||||
|
its push of the git-annex branch (as does the assistant). I considered but
|
||||||
|
rejected having sync do the kind of uuid-tagged branch push that the
|
||||||
|
assistant sometimes falls back to if it's failing to do a normal sync. It's
|
||||||
|
ugly, but worse, it wouldn't work in the workflow where multiple clients
|
||||||
|
are syncing to a central bare repository, because they'd not pull down the
|
||||||
|
hidden uuid-tagged branches, and without the assistant running on the
|
||||||
|
repository, nothing would ever merge their data into the git-annex branch.
|
||||||
|
Forcing the push of synced/git-annex was easy, once I satisfied myself
|
||||||
|
that it was always ok to do so.
|
||||||
|
|
||||||
|
Also factored out a module that knows about all the different log files
|
||||||
|
stored on the git-annex branch, which is all the support infrastructure
|
||||||
|
that will be needed to make `git annex forget --drop-dead` work. Since this
|
||||||
|
is basically a routing module, perhaps I'll get around to making it use
|
||||||
|
a nice bidirectional routing library like
|
||||||
|
[Zwaluw](http://hackage.haskell.org/package/Zwaluw) one day.
|
|
@ -0,0 +1,8 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="Sandra.Devil"
|
||||||
|
ip="77.172.73.184"
|
||||||
|
subject="New laptop"
|
||||||
|
date="2013-09-01T09:38:32Z"
|
||||||
|
content="""
|
||||||
|
What is the new laptop you are going to use? Specs please :)
|
||||||
|
"""]]
|
11
doc/devblog/day_1__inauspicious_beginning.mdwn
Normal file
11
doc/devblog/day_1__inauspicious_beginning.mdwn
Normal file
|
@ -0,0 +1,11 @@
|
||||||
|
I try hard to keep this devblog about git-annex development and not me.
|
||||||
|
However, it is a shame that what I wanted to be the beginning of my first
|
||||||
|
real month of work funded by the new campaign has been marred by my home's
|
||||||
|
internet connection being taken out by a lightning strike, and by illness.
|
||||||
|
Nearly back on my feet after that, and waiting for my new laptop to
|
||||||
|
finally get here.
|
||||||
|
|
||||||
|
Today's work: Finished up the `git annex forget` feature and merged it in.
|
||||||
|
Fixed the bug that was causing the commit race detection code to
|
||||||
|
incorrectly fire on the commit made by the transition code. Few other bits
|
||||||
|
and pieces.
|
|
@ -0,0 +1,10 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="rjc"
|
||||||
|
ip="86.22.66.200"
|
||||||
|
subject="laptop"
|
||||||
|
date="2013-09-04T21:42:52Z"
|
||||||
|
content="""
|
||||||
|
Are you retiring your Dell mini?
|
||||||
|
|
||||||
|
What kind of laptop are you getting?
|
||||||
|
"""]]
|
|
@ -0,0 +1,8 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="http://pnijjar.livejournal.com/"
|
||||||
|
ip="99.236.22.229"
|
||||||
|
subject="comment 1"
|
||||||
|
date="2013-08-31T00:05:16Z"
|
||||||
|
content="""
|
||||||
|
Do we need to update our RSS feeds? I appear to be getting your devblog posts in my old feed, but I do not know whether that will continue working.
|
||||||
|
"""]]
|
|
@ -0,0 +1,10 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="https://www.google.com/accounts/o8/id?id=AItOawmkBwMWvNKZZCge_YqobCSILPMeK6xbFw8"
|
||||||
|
nickname="develop"
|
||||||
|
subject="comment 2"
|
||||||
|
date="2013-08-31T10:03:04Z"
|
||||||
|
content="""
|
||||||
|
The old RSS feed will continue working.
|
||||||
|
|
||||||
|
So sit back, relax, and enjoy the show.
|
||||||
|
"""]]
|
|
@ -0,0 +1,10 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="https://me.yahoo.com/a/2grhJvAC049fJnvALDXek.6MRZMTlg--#eec89"
|
||||||
|
nickname="John"
|
||||||
|
subject="comment 4"
|
||||||
|
date="2013-08-30T06:06:16Z"
|
||||||
|
content="""
|
||||||
|
Just to confirm, this wasn't a git-annex problem at all, but just a misstep during migration as you suggested.
|
||||||
|
|
||||||
|
I think what I'm going to do now is to just wipe the slate clean and start over again, by using `unannex -fast` on all the files, wiping `.git`, and then adding everything back in using my new default backend of SHA512E. The bigger pain is doing the same thing on all the servers where I have this data (to avoid having to upload it again), but in such a way that I'm not replicating file history. I think I should be able to just clone, `mv $OLDREPO/.git/annex/objects objects`, `git annex add objects`, `git rm -r --cached objects`, and then everything should be good without even needing a new commit on the remote machine, just a git-annex sync.
|
||||||
|
"""]]
|
|
@ -0,0 +1,72 @@
|
||||||
|
I've been experiencing problems with Box.com for a few days now and I don't know what's causing them. Is anyone else experiencing anything similar?
|
||||||
|
|
||||||
|
I paste the log.
|
||||||
|
|
||||||
|
[2013-09-02 12:27:26 CEST] TransferWatcher: transfer finishing: Transfer {transferDirection = Upload, transferUUID = UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9", transferKey = Key {keyName = "c9e1d5421e78924c21e3d68e84f80a8d1f64f9488020107ca0eeee0c4f10e763.py", keyBackendName = "SHA256E", keySize = Just 1891, keyMtime = Nothing}}
|
||||||
|
[2013-09-02 12:27:26 CEST] TransferScanner: queued Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/kgp/kant.xml Nothing : expensive scan found missing object
|
||||||
|
[2013-09-02 12:27:26 CEST] Transferrer: Transferring: Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/argecho.py Nothing
|
||||||
|
[2013-09-02 12:27:26 CEST] TransferWatcher: transfer starting: Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/argecho.py Nothing
|
||||||
|
[2013-09-02 12:27:26 CEST] TransferWatcher: transfer starting: Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/argecho.py Nothing
|
||||||
|
|
||||||
|
|
||||||
|
100% 0.0 B/s 0s[2013-09-02 12:27:26 CEST] TransferWatcher: transfer starting: Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/argecho.py Just 437
|
||||||
|
ResponseTimeout
|
||||||
|
ResponseTimeout
|
||||||
|
|
||||||
|
|
||||||
|
[2013-09-02 12:27:44 CEST] TransferWatcher: transfer finishing: Transfer {transferDirection = Upload, transferUUID = UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9", transferKey = Key {keyName = "dd3cc45d91430c6f7d68eb807f4ac1561cd0297b11a2de77b5fe66017d125798.py", keyBackendName = "SHA256E", keySize = Just 437, keyMtime = Nothing}}
|
||||||
|
[2013-09-02 12:27:44 CEST] TransferScanner: queued Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/kgp/kgp.dtd Nothing : expensive scan found missing object
|
||||||
|
[2013-09-02 12:27:44 CEST] Transferrer: Transferring: Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/autosize.py Nothing
|
||||||
|
[2013-09-02 12:27:44 CEST] TransferWatcher: transfer starting: Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/autosize.py Nothing
|
||||||
|
[2013-09-02 12:27:44 CEST] TransferWatcher: transfer starting: Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/autosize.py Nothing
|
||||||
|
|
||||||
|
|
||||||
|
100% 0.0 B/s 0s[2013-09-02 12:27:44 CEST] TransferWatcher: transfer starting: Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/autosize.py Just 2861
|
||||||
|
ResponseTimeout
|
||||||
|
ResponseTimeout
|
||||||
|
|
||||||
|
|
||||||
|
[2013-09-02 12:28:02 CEST] TransferWatcher: transfer finishing: Transfer {transferDirection = Upload, transferUUID = UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9", transferKey = Key {keyName = "d6b7940ac68768a8e37e72f248e2d94f19fb0d47062084d9baf0ec08cebbf692.py", keyBackendName = "SHA256E", keySize = Just 2861, keyMtime = Nothing}}
|
||||||
|
[2013-09-02 12:28:02 CEST] TransferScanner: queued Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/kgp/kgp.py Nothing : expensive scan found missing object
|
||||||
|
[2013-09-02 12:28:02 CEST] Transferrer: Transferring: Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/builddialectexamples.py Nothing
|
||||||
|
[2013-09-02 12:28:03 CEST] TransferWatcher: transfer starting: Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/builddialectexamples.py Nothing
|
||||||
|
[2013-09-02 12:28:03 CEST] TransferWatcher: transfer starting: Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/builddialectexamples.py Nothing
|
||||||
|
|
||||||
|
|
||||||
|
100% 0.0 B/s 0s[2013-09-02 12:28:03 CEST] TransferWatcher: transfer starting: Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/builddialectexamples.py Just 1090
|
||||||
|
ResponseTimeout
|
||||||
|
ResponseTimeout
|
||||||
|
|
||||||
|
|
||||||
|
[2013-09-02 12:28:21 CEST] TransferWatcher: transfer finishing: Transfer {transferDirection = Upload, transferUUID = UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9", transferKey = Key {keyName = "f1492b80d05b96cc7cf2904d461c99d430fa86a4eb1d99f1b155c9147ff4420f.py", keyBackendName = "SHA256E", keySize = Just 1090, keyMtime = Nothing}}
|
||||||
|
[2013-09-02 12:28:21 CEST] TransferScanner: queued Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/kgp/russiansample.xml Nothing : expensive scan found missing object
|
||||||
|
[2013-09-02 12:28:21 CEST] Transferrer: Transferring: Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/colorize.py Nothing
|
||||||
|
[2013-09-02 12:28:21 CEST] TransferWatcher: transfer starting: Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/colorize.py Nothing
|
||||||
|
[2013-09-02 12:28:21 CEST] TransferWatcher: transfer starting: Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/colorize.py Nothing
|
||||||
|
|
||||||
|
|
||||||
|
100% 0.0 B/s 0s[2013-09-02 12:28:21 CEST] TransferWatcher: transfer starting: Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/colorize.py Just 4864
|
||||||
|
ResponseTimeout
|
||||||
|
ResponseTimeout
|
||||||
|
|
||||||
|
|
||||||
|
[2013-09-02 12:28:40 CEST] TransferWatcher: transfer finishing: Transfer {transferDirection = Upload, transferUUID = UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9", transferKey = Key {keyName = "b577eaf8b6ddbf9fef866c455cae248aec3b22e3f2e91aa2b75ece90f1801689.py", keyBackendName = "SHA256E", keySize = Just 4864, keyMtime = Nothing}}
|
||||||
|
[2013-09-02 12:28:40 CEST] TransferScanner: queued Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/kgp/stderr.py Nothing : expensive scan found missing object
|
||||||
|
[2013-09-02 12:28:40 CEST] Transferrer: Transferring: Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/dialect.py Nothing
|
||||||
|
[2013-09-02 12:28:40 CEST] TransferWatcher: transfer starting: Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/dialect.py Nothing
|
||||||
|
[2013-09-02 12:28:40 CEST] TransferWatcher: transfer starting: Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/dialect.py Nothing
|
||||||
|
|
||||||
|
|
||||||
|
100% 0.0 B/s 0s[2013-09-02 12:28:40 CEST] TransferWatcher: transfer starting: Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/dialect.py Just 4449
|
||||||
|
ResponseTimeout
|
||||||
|
ResponseTimeout
|
||||||
|
|
||||||
|
|
||||||
|
[2013-09-02 12:28:58 CEST] TransferWatcher: transfer finishing: Transfer {transferDirection = Upload, transferUUID = UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9", transferKey = Key {keyName = "c5e5d9b1bee2710c7ed05270a363d3e93270b0fb6779c4c8d59ace06c11db684.py", keyBackendName = "SHA256E", keySize = Just 4449, keyMtime = Nothing}}
|
||||||
|
[2013-09-02 12:28:58 CEST] TransferScanner: queued Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/kgp/stdout.py Nothing : expensive scan found missing object
|
||||||
|
[2013-09-02 12:28:58 CEST] Transferrer: Transferring: Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/fibonacci.py Nothing
|
||||||
|
[2013-09-02 12:28:58 CEST] TransferWatcher: transfer starting: Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/fibonacci.py Nothing
|
||||||
|
[2013-09-02 12:28:58 CEST] TransferWatcher: transfer starting: Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/fibonacci.py Nothing
|
||||||
|
|
||||||
|
|
||||||
|
100% 0.0 B/s 0s[2013-09-02 12:28:58 CEST] TransferWatcher: transfer starting: Upload UUID "72111b4c-28fe-42fd-a77b-e4cb9240a1c9" Documentos/diveintopython-5.4/py/fibonacci.py Just 532
|
|
@ -0,0 +1,8 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="http://sunny256.sunbase.org/"
|
||||||
|
nickname="sunny256"
|
||||||
|
subject="It works here"
|
||||||
|
date="2013-09-02T11:47:00Z"
|
||||||
|
content="""
|
||||||
|
I set up a box.com remote a couple of months ago or so just for testing. Haven't used it that much, but I tested it now to see if it still works. No errors or problems. I have pasted the output from a session where I copied a file to box.com, dropped it locally, then got it back from box.com here: <https://gist.github.com/sunny256/6411972>. The computer I ran the test on is using the newest git-annex binary (v4.20130827), Ubuntu 10.04.4 LTS. Pretty old distro, but it still works.
|
||||||
|
"""]]
|
177
doc/forum/Help_Windows_walkthrough.mdwn
Normal file
177
doc/forum/Help_Windows_walkthrough.mdwn
Normal file
|
@ -0,0 +1,177 @@
|
||||||
|
Hello,
|
||||||
|
|
||||||
|
i am trying to run the walkthrough on Windows 7. When i try to get the contents of a file, i only get a some git annex text string and not the real file. Both repositories are on the same ntfs filesystem.
|
||||||
|
|
||||||
|
C:\tmp>git annex version
|
||||||
|
git-annex version: 4.20130827-g4f18612
|
||||||
|
build flags: Pairing Testsuite S3 WebDAV DNS
|
||||||
|
local repository version: 4
|
||||||
|
default repository version: 3
|
||||||
|
supported repository versions: 3 4
|
||||||
|
upgrade supported from repository versions: 2
|
||||||
|
|
||||||
|
C:\tmp\server>git --version
|
||||||
|
git version 1.8.3.msysgit.0
|
||||||
|
|
||||||
|
|
||||||
|
# walkthrough.bat
|
||||||
|
|
||||||
|
doskey /history > commands.log
|
||||||
|
mkdir laptop
|
||||||
|
cd laptop
|
||||||
|
git init
|
||||||
|
git annex init laptop
|
||||||
|
cd ..
|
||||||
|
|
||||||
|
git clone laptop server
|
||||||
|
cd server
|
||||||
|
git annex init server
|
||||||
|
git remote add laptop c:\tmp\laptop
|
||||||
|
|
||||||
|
cd ..\laptop
|
||||||
|
git remote add server c:\tmp\server
|
||||||
|
copy ..\1.pdf .
|
||||||
|
git annex add 1.pdf
|
||||||
|
git commit -m add
|
||||||
|
dir
|
||||||
|
|
||||||
|
cd ..\server
|
||||||
|
dir
|
||||||
|
git fetch laptop
|
||||||
|
git merge laptop/master
|
||||||
|
git annex get 1.pdf
|
||||||
|
dir
|
||||||
|
type 1.pdf
|
||||||
|
|
||||||
|
|
||||||
|
# walkthrough.log
|
||||||
|
|
||||||
|
C:\tmp>walkthrough.bat
|
||||||
|
|
||||||
|
C:\tmp>doskey /history 1>commands.log
|
||||||
|
|
||||||
|
C:\tmp>mkdir laptop
|
||||||
|
|
||||||
|
C:\tmp>cd laptop
|
||||||
|
|
||||||
|
C:\tmp\laptop>git init
|
||||||
|
Initialized empty Git repository in C:/tmp/laptop/.git/
|
||||||
|
|
||||||
|
C:\tmp\laptop>git annex init laptop
|
||||||
|
init laptop
|
||||||
|
Detected a crippled filesystem.
|
||||||
|
|
||||||
|
Enabling direct mode.
|
||||||
|
|
||||||
|
Detected a filesystem without fifo support.
|
||||||
|
|
||||||
|
Disabling ssh connection caching.
|
||||||
|
ok
|
||||||
|
(Recording state in git...)
|
||||||
|
|
||||||
|
C:\tmp\laptop>cd ..
|
||||||
|
|
||||||
|
C:\tmp>git clone laptop server
|
||||||
|
Cloning into 'server'...
|
||||||
|
done.
|
||||||
|
warning: remote HEAD refers to nonexistent ref, unable to checkout.
|
||||||
|
|
||||||
|
|
||||||
|
C:\tmp>cd server
|
||||||
|
|
||||||
|
C:\tmp\server>git annex init server
|
||||||
|
init server
|
||||||
|
Detected a crippled filesystem.
|
||||||
|
|
||||||
|
Enabling direct mode.
|
||||||
|
|
||||||
|
Detected a filesystem without fifo support.
|
||||||
|
|
||||||
|
Disabling ssh connection caching.
|
||||||
|
ok
|
||||||
|
(Recording state in git...)
|
||||||
|
|
||||||
|
C:\tmp\server>git remote add laptop c:\tmp\laptop
|
||||||
|
|
||||||
|
C:\tmp\server>cd ..\laptop
|
||||||
|
|
||||||
|
C:\tmp\laptop>git remote add server c:\tmp\server
|
||||||
|
|
||||||
|
C:\tmp\laptop>copy ..\1.pdf .
|
||||||
|
1 file(s) copied.
|
||||||
|
|
||||||
|
C:\tmp\laptop>git annex add 1.pdf
|
||||||
|
add 1.pdf (checksum...) ok
|
||||||
|
(Recording state in git...)
|
||||||
|
|
||||||
|
C:\tmp\laptop>git commit -m add
|
||||||
|
[master (root-commit) 7ad1514] add
|
||||||
|
1 file changed, 1 insertion(+)
|
||||||
|
create mode 120000 1.pdf
|
||||||
|
|
||||||
|
C:\tmp\laptop>dir
|
||||||
|
Volume in drive C has no label.
|
||||||
|
Volume Serial Number is x
|
||||||
|
|
||||||
|
Directory of C:\tmp\laptop
|
||||||
|
|
||||||
|
09/01/2013 11:03 AM <DIR> .
|
||||||
|
09/01/2013 11:03 AM <DIR> ..
|
||||||
|
08/30/2013 12:43 PM 37,500 1.pdf
|
||||||
|
1 File(s) 37,500 bytes
|
||||||
|
2 Dir(s) 7,698,817,024 bytes free
|
||||||
|
|
||||||
|
C:\tmp\laptop>cd ..\server
|
||||||
|
|
||||||
|
C:\tmp\server>dir
|
||||||
|
Volume in drive C has no label.
|
||||||
|
Volume Serial Number is x
|
||||||
|
|
||||||
|
Directory of C:\tmp\server
|
||||||
|
|
||||||
|
09/01/2013 11:03 AM <DIR> .
|
||||||
|
09/01/2013 11:03 AM <DIR> ..
|
||||||
|
0 File(s) 0 bytes
|
||||||
|
2 Dir(s) 7,698,817,024 bytes free
|
||||||
|
|
||||||
|
C:\tmp\server>git fetch laptop
|
||||||
|
remote: Counting objects: 9, done.
|
||||||
|
remote: Compressing objects: 100% (6/6), done.
|
||||||
|
remote: Total 8 (delta 1), reused 0 (delta 0)
|
||||||
|
Unpacking objects: 100% (8/8), done.
|
||||||
|
From c:\tmp\laptop
|
||||||
|
* [new branch] git-annex -> laptop/git-annex
|
||||||
|
* [new branch] master -> laptop/master
|
||||||
|
|
||||||
|
C:\tmp\server>git merge laptop/master
|
||||||
|
|
||||||
|
C:\tmp\server>git annex get 1.pdf
|
||||||
|
get 1.pdf (merging laptop/git-annex origin/git-annex into git-annex...)
|
||||||
|
(Recording state in git...)
|
||||||
|
(from laptop...)
|
||||||
|
1.pdf
|
||||||
|
37500 100% 4.51MB/s 0:00:00 (xfer#1, to-check=0/1)
|
||||||
|
|
||||||
|
sent 37573 bytes received 31 bytes 75208.00 bytes/sec
|
||||||
|
total size is 37500 speedup is 1.00
|
||||||
|
ok
|
||||||
|
(Recording state in git...)
|
||||||
|
|
||||||
|
C:\tmp\server>dir
|
||||||
|
Volume in drive C has no label.
|
||||||
|
Volume Serial Number is x
|
||||||
|
|
||||||
|
Directory of C:\tmp\server
|
||||||
|
|
||||||
|
09/01/2013 11:03 AM <DIR> .
|
||||||
|
09/01/2013 11:03 AM <DIR> ..
|
||||||
|
09/01/2013 11:03 AM 194 1.pdf
|
||||||
|
1 File(s) 194 bytes
|
||||||
|
2 Dir(s) 7,698,767,872 bytes free
|
||||||
|
|
||||||
|
C:\tmp\server>type 1.pdf
|
||||||
|
.git/annex/objects/kM/0q/SHA256E-s37500--32d8190c7e189d45f48245a100e4cc981ea1bbc
|
||||||
|
02ac8bfa6188db73e41ce06f3.pdf/SHA256E-s37500--32d8190c7e189d45f48245a100e4cc981e
|
||||||
|
a1bbc02ac8bfa6188db73e41ce06f3.pdfC:\tmp\server>
|
||||||
|
C:\tmp\server>
|
||||||
|
|
|
@ -0,0 +1,12 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="http://joeyh.name/"
|
||||||
|
ip="4.153.8.7"
|
||||||
|
subject="comment 1"
|
||||||
|
date="2013-09-03T17:59:03Z"
|
||||||
|
content="""
|
||||||
|
The walkthrough assumes a system that uses indirect mode by default, so it won't work quite right on Windows, which is forced to use direct mode.
|
||||||
|
|
||||||
|
Running `git annex fsck` in the server repository will fix up this situation, but the right thing on Windows is to use `git annex sync` rather than the manual `git fetch + git merge` the walkthrough shows.
|
||||||
|
|
||||||
|
Guess I'll make the walkthrough use sync, although it may make it harder for people to understand what's going on internally.
|
||||||
|
"""]]
|
|
@ -0,0 +1,14 @@
|
||||||
|
Hello,
|
||||||
|
|
||||||
|
I want to be safe and have two copies of my files on two different backend. Currently I only have a SSH backend, that stores all my data. I have full(root) access to that machine/backend. On my laptop I have only a few bytes of data, because all is moved/copied to that SSH backend. Now, I want to duplicate the data on the SSH backend to a Google Drive account (or any other). How could I do that (without downloading all data from the SSH backend)??? Encryption is not a must.
|
||||||
|
|
||||||
|
I looked into the annex/objects folder on the SSH backend, but there are 3 char length directories compared to what I see on a test Google Drive backend, where only 2 char length directory names are.
|
||||||
|
|
||||||
|
Example SSH backend: [git-annex root]/annex/objects/c10/90a/SHA256E-s445227--14c3f85d6dd3464f116f6a5bbd411012781d36794549d136b18d1914c4158820.jpg/SHA256E-s445227--14c3f85d6dd3464f116f6a5bbd411012781d36794549d136b18d1914c4158820.jpg
|
||||||
|
|
||||||
|
Example Google Drive: [Google Drive root]/annex/W7/xQ/SHA256E-s913904--29f9800b0dd34d4200c4e9ee152b79c3556a9a473848720be7cf83d20eff65a4.JPG
|
||||||
|
|
||||||
|
Is there a way to convert these directory names and do a simpe copy???
|
||||||
|
|
||||||
|
Thank you,
|
||||||
|
Bence
|
|
@ -0,0 +1,12 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="http://joeyh.name/"
|
||||||
|
ip="2001:4830:1600:187::2"
|
||||||
|
subject="comment 2"
|
||||||
|
date="2013-09-04T06:43:26Z"
|
||||||
|
content="""
|
||||||
|
Recently git-annex has gotten the ability to do this: `git annex forget --drop-dead`
|
||||||
|
|
||||||
|
That prunes all history relating to all dead remotes. You need to be running a git-annex that supports this on all computers you use the repos on, or the pruned history will get merged back in.
|
||||||
|
|
||||||
|
I don't recommend doing this just because you want to \"clean history\". Think of it as something you can do at some point in the future if the .git/objects somehow gets too large or too slow. Put off deleting data until tomorrow if you don't absolutely need to do it today.
|
||||||
|
"""]]
|
|
@ -0,0 +1,14 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="konubinix"
|
||||||
|
ip="82.243.233.186"
|
||||||
|
subject="Dropping dead repositories"
|
||||||
|
date="2013-09-04T07:40:22Z"
|
||||||
|
content="""
|
||||||
|
Actually, it may be a good idea to remove repositories made for tests purposes.
|
||||||
|
|
||||||
|
I now have 2 dead repositories that are USB_test1 and USB_test2 that I created before knowing I could reuse the annex uuid.
|
||||||
|
|
||||||
|
They are now there and it is difficult to remove them.
|
||||||
|
|
||||||
|
For that special case, the --drop-dead feature is very welcome.
|
||||||
|
"""]]
|
|
@ -0,0 +1,8 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="https://me.yahoo.com/a/2grhJvAC049fJnvALDXek.6MRZMTlg--#eec89"
|
||||||
|
nickname="John"
|
||||||
|
subject="comment 1"
|
||||||
|
date="2013-08-29T07:23:13Z"
|
||||||
|
content="""
|
||||||
|
Maybe one way to solve this that would be general is to have some kind of `prune-history` command, which keeps only the HEAD and drops everything else. Because there are some repositories that I want to manage with `git-annex` for many reasons, but I don't care about keep history around at all.
|
||||||
|
"""]]
|
|
@ -0,0 +1,8 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="https://me.yahoo.com/a/2grhJvAC049fJnvALDXek.6MRZMTlg--#eec89"
|
||||||
|
nickname="John"
|
||||||
|
subject="comment 2"
|
||||||
|
date="2013-08-30T06:18:42Z"
|
||||||
|
content="""
|
||||||
|
This was answered quite thoroughly in:http://git-annex.branchable.com/forum/safely_dropping_git-annex_history/
|
||||||
|
"""]]
|
|
@ -0,0 +1,8 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="http://joeyh.name/"
|
||||||
|
ip="2001:4830:1600:187::2"
|
||||||
|
subject="comment 3"
|
||||||
|
date="2013-09-04T06:36:15Z"
|
||||||
|
content="""
|
||||||
|
`git annex forget` automates this now. Needs a version of git-annex supporting it installed on *all* the computers you use the repo on.
|
||||||
|
"""]]
|
|
@ -0,0 +1,14 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="https://www.google.com/accounts/o8/id?id=AItOawnRai_qFYPVvEgC6i1nlM1bh-C__jbhqS0"
|
||||||
|
nickname="Matthew"
|
||||||
|
subject="Looks great"
|
||||||
|
date="2013-08-29T12:45:10Z"
|
||||||
|
content="""
|
||||||
|
This looks great as I have:
|
||||||
|
|
||||||
|
* A preference for multiple small repositories.
|
||||||
|
* Old versions for `git-annex` due to being on Ubuntu LTS for my server.
|
||||||
|
* A Samsung Galaxy Nexus which somehow seems too slow to run the assistant.
|
||||||
|
|
||||||
|
So these steps combined with some locking and maybe `inotify` seem perfect
|
||||||
|
"""]]
|
|
@ -0,0 +1,10 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="http://joeyh.name/"
|
||||||
|
ip="2001:4830:1600:187::2"
|
||||||
|
subject="comment 4"
|
||||||
|
date="2013-09-04T06:44:42Z"
|
||||||
|
content="""
|
||||||
|
Status no longer shows dead repositories.
|
||||||
|
|
||||||
|
See also, answer here: <http://git-annex.branchable.com/forum/How_to_delete_a_remote__63__/#comment-7ebf3804709a5aa64f1ca057a7df74f9>
|
||||||
|
"""]]
|
|
@ -0,0 +1,20 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="arand"
|
||||||
|
ip="130.243.226.21"
|
||||||
|
subject="comment 4"
|
||||||
|
date="2013-09-01T18:06:51Z"
|
||||||
|
content="""
|
||||||
|
Yet another solution, keeping it all in one script
|
||||||
|
|
||||||
|
#!/bin/sh
|
||||||
|
|
||||||
|
while IFS= read line
|
||||||
|
do
|
||||||
|
test -n \"${line%%#*}\" && echo git annex importfeed --relaxed \"$line\"
|
||||||
|
done <<EOF
|
||||||
|
# FooCast - Alice & Bob
|
||||||
|
http://feeds.foo.com/foocast
|
||||||
|
# FrobCast
|
||||||
|
http://meep.moop.com/feed
|
||||||
|
EOF
|
||||||
|
"""]]
|
|
@ -0,0 +1,8 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="http://joeyh.name/"
|
||||||
|
ip="2001:4830:1600:187::2"
|
||||||
|
subject="comment 12"
|
||||||
|
date="2013-09-04T06:38:00Z"
|
||||||
|
content="""
|
||||||
|
`git annex forget` automates this now, without needing to force-push or have a flag day. Needs a version of git-annex supporting it installed on *all* the computers you use the repo on. Repos notice they need to forget when git annex is run in them, and do, automatically.
|
||||||
|
"""]]
|
|
@ -503,6 +503,23 @@ subdirectories).
|
||||||
|
|
||||||
Upgrades the repository to current layout.
|
Upgrades the repository to current layout.
|
||||||
|
|
||||||
|
* forget
|
||||||
|
|
||||||
|
Causes the git-annex branch to be rewritten, throwing away historical
|
||||||
|
data about past locations of files. The resulting branch will use less
|
||||||
|
space, but `git annex log` will not be able to show where
|
||||||
|
files used to be located.
|
||||||
|
|
||||||
|
To also prune references to repositories that have been marked as dead,
|
||||||
|
specify --drop-dead.
|
||||||
|
|
||||||
|
When this rewritten branch is merged into other clones of
|
||||||
|
the repository, git-annex will automatically perform the same rewriting
|
||||||
|
to their local git-annex branches. So the forgetfulness will automatically
|
||||||
|
propigate out from its starting point until all repositories running
|
||||||
|
git-annex have forgotten their old history. (You may need to force
|
||||||
|
git to push the branch to any git repositories not running git-annex.
|
||||||
|
|
||||||
# QUERY COMMANDS
|
# QUERY COMMANDS
|
||||||
|
|
||||||
* version
|
* version
|
||||||
|
|
|
@ -0,0 +1,10 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="RaspberryPie"
|
||||||
|
ip="96.47.226.20"
|
||||||
|
subject="git-annex assistant for the Raspberry Pi"
|
||||||
|
date="2013-09-04T03:58:37Z"
|
||||||
|
content="""
|
||||||
|
It took a while and a few tries, but I finally built the git-annex binary including the assistant on a Raspberry Pi. The build comes without the flags webapp, webdav, and dbus as these rely on a Template Haskell compiler that hasn't been ported to Arm architecture yet.
|
||||||
|
|
||||||
|
I put the binary up on Github in case anyone's interested: <https://github.com/tradloff/git-annex-RPi>
|
||||||
|
"""]]
|
|
@ -0,0 +1,11 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="http://sunny256.sunbase.org/"
|
||||||
|
nickname="sunny256"
|
||||||
|
subject="Missing from the downloads.kitenet.net annex"
|
||||||
|
date="2013-08-29T18:05:38Z"
|
||||||
|
content="""
|
||||||
|
Great release, thanks a lot. It's missing from the annex at downloads.kitenet.net, though.
|
||||||
|
|
||||||
|
Cheers,<br />
|
||||||
|
Øyvind (sunny256)
|
||||||
|
"""]]
|
|
@ -0,0 +1,25 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="http://joeyh.name/"
|
||||||
|
ip="4.153.8.7"
|
||||||
|
subject="comment 2"
|
||||||
|
date="2013-08-29T18:26:00Z"
|
||||||
|
content="""
|
||||||
|
It seems to be there on downloads.kitenet.net. When I run `git log` in there I see commit 82de1ed1a354e389bc71a15af1a3e67b5bd56f23 which added the release to the annex, and all the files seem to be present. For example, git-annex-standalone-amd64.tar.gz is pointing at the key `SHA256E-s20143752--388c33138185fb2eb5fdb00bf2155a9168e5a76501216887ea1ffa7ada06b776.tar.gz`, which is right.
|
||||||
|
|
||||||
|
<pre>
|
||||||
|
joey@wren:~>wget http://downloads.kitenet.net/git-annex/linux/current/git-annex-standalone-amd64.tar.gz
|
||||||
|
--2013-08-29 14:25:00-- http://downloads.kitenet.net/git-annex/linux/current/git-annex-standalone-amd64.tar.gz
|
||||||
|
Resolving downloads.kitenet.net (downloads.kitenet.net)... 2001:41c8:125:49::10, 80.68.85.49
|
||||||
|
Connecting to downloads.kitenet.net (downloads.kitenet.net)|2001:41c8:125:49::10|:80... connected.
|
||||||
|
HTTP request sent, awaiting response... 200 OK
|
||||||
|
Length: 20143752 (19M) [application/x-gzip]
|
||||||
|
Saving to: ‘git-annex-standalone-amd64.tar.gz’
|
||||||
|
|
||||||
|
100%[======================================>] 20,143,752 48.9MB/s in 0.4s
|
||||||
|
|
||||||
|
2013-08-29 14:25:01 (48.9 MB/s) - ‘git-annex-standalone-amd64.tar.gz’ saved [20143752/20143752]
|
||||||
|
|
||||||
|
joey@wren:~>sha256sum git-annex-standalone-amd64.tar.gz
|
||||||
|
388c33138185fb2eb5fdb00bf2155a9168e5a76501216887ea1ffa7ada06b776 git-annex-standalone-amd64.tar.gz
|
||||||
|
</pre>
|
||||||
|
"""]]
|
|
@ -0,0 +1,39 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="http://sunny256.sunbase.org/"
|
||||||
|
nickname="sunny256"
|
||||||
|
subject="comment 3"
|
||||||
|
date="2013-08-30T11:43:44Z"
|
||||||
|
content="""
|
||||||
|
Hm, commit 82de1ed1a3 doesn't exist here after git-annex sync. This is the output from another computer, running Linux Mint 15:
|
||||||
|
|
||||||
|
$ ga sync
|
||||||
|
commit
|
||||||
|
ok
|
||||||
|
pull linode
|
||||||
|
ok
|
||||||
|
pull kitenet
|
||||||
|
WARNING: gnome-keyring:: couldn't connect to: /run/user/sunny/keyring-WSsS6N/pkcs11: No such file or directory
|
||||||
|
ok
|
||||||
|
push linode
|
||||||
|
Everything up-to-date
|
||||||
|
ok
|
||||||
|
push kitenet
|
||||||
|
WARNING: gnome-keyring:: couldn't connect to: /run/user/sunny/keyring-WSsS6N/pkcs11: No such file or directory
|
||||||
|
WARNING: gnome-keyring:: couldn't connect to: /run/user/sunny/keyring-WSsS6N/pkcs11: No such file or directory
|
||||||
|
error: Cannot access URL http://downloads.kitenet.net/.git/, return code 22
|
||||||
|
fatal: git-http-push failed
|
||||||
|
failed
|
||||||
|
git-annex: sync: 1 failed
|
||||||
|
$ git log -1
|
||||||
|
commit e4d2f03d9b37b2fac9508bf755ff7619bf46590c (HEAD, linode/synced/master, linode/master, linode/HEAD, kitenet/synced/master, kitenet/master, synced/master, master)
|
||||||
|
Author: Joey Hess <joey@kitenet.net>
|
||||||
|
Date: 3 weeks ago
|
||||||
|
|
||||||
|
update
|
||||||
|
2013-08-30 13:36:37 sunny@passp:~/src/other/annex/downloads.kitenet.net/git-annex (master u=)
|
||||||
|
$ git log 82de1ed1a354e389bc71a15af1a3e67b5bd56f23
|
||||||
|
fatal: bad object 82de1ed1a354e389bc71a15af1a3e67b5bd56f23
|
||||||
|
|
||||||
|
There's some warnings from gnome-keyring and a failed push (sorry about that, happens automatically), but the fetch from kitenet seems to succeed.
|
||||||
|
|
||||||
|
"""]]
|
|
@ -0,0 +1,8 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="http://sunny256.sunbase.org/"
|
||||||
|
nickname="sunny256"
|
||||||
|
subject="comment 4"
|
||||||
|
date="2013-08-30T11:49:20Z"
|
||||||
|
content="""
|
||||||
|
And some additional info, I'm using `http://downloads.kitenet.net/.git/` as the address to your annex. Maybe this repo is missing a `git update-server-info` in the `post-update` hook or something.
|
||||||
|
"""]]
|
|
@ -0,0 +1,10 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="http://joeyh.name/"
|
||||||
|
ip="4.153.8.7"
|
||||||
|
subject="sorry for delay.."
|
||||||
|
date="2013-09-03T18:07:34Z"
|
||||||
|
content="""
|
||||||
|
That's weird.. I have a post-update hook that runs git-update-server-info, but I reproduced the problem, and manually running that fixed it.
|
||||||
|
|
||||||
|
Guess I will need to keep an eye on this at the next release to see if it was a one-off problem..
|
||||||
|
"""]]
|
|
@ -0,0 +1,12 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="https://www.google.com/accounts/o8/id?id=AItOawmTNrhkVQ26GBLaLD5-zNuEiR8syTj4mI8"
|
||||||
|
nickname="Juan"
|
||||||
|
subject="comment 10"
|
||||||
|
date="2013-08-31T18:20:58Z"
|
||||||
|
content="""
|
||||||
|
I'm already spreading the word. Handling scientific papers, data, simulations and code has been quite a challenge during my academic career. While code was solved long ago, the three first items remained a huge problem.
|
||||||
|
I'm sure many of my colleagues will be happy to use it.
|
||||||
|
Is there any hashtag or twitter account? I've seen that you collected some of my tweets, but I don't know how you did it. Did you search for git-annex?
|
||||||
|
Best,
|
||||||
|
Juan
|
||||||
|
"""]]
|
|
@ -9,18 +9,20 @@ Here's how I set it up. --[[Joey]]
|
||||||
1. Set up a web site. I used Apache, and configured it to follow symlinks.
|
1. Set up a web site. I used Apache, and configured it to follow symlinks.
|
||||||
`Options FollowSymLinks`
|
`Options FollowSymLinks`
|
||||||
2. Put some files on the website. Make sure it works.
|
2. Put some files on the website. Make sure it works.
|
||||||
4. `git init; git annex init`
|
3. `git init; git annex init`
|
||||||
3. We want users to be able to clone the git repository over http, because
|
4. `git config core.sharedrepository world` (Makes sure files
|
||||||
|
are always added with permissions that allow everyone to read them.)
|
||||||
|
5. We want users to be able to clone the git repository over http, because
|
||||||
git-annex can download files from it over http as well. For this to
|
git-annex can download files from it over http as well. For this to
|
||||||
work, `git update-server-info` needs to get run after commits. The
|
work, `git update-server-info` needs to get run after commits. The
|
||||||
git `post-update` hook will take care of this, you just need to enable
|
git `post-update` hook will take care of this, you just need to enable
|
||||||
the hook. `chmod +x .git/hooks/post-update`
|
the hook. `chmod +x .git/hooks/post-update`
|
||||||
5. `git annex add; git commit -m added`
|
6. `git annex add; git commit -m added`
|
||||||
6. Make sure users can still download files from the site directly.
|
7. Make sure users can still download files from the site directly.
|
||||||
7. Instruct advanced users to clone a http url that ends with the "/.git/"
|
8. Instruct advanced users to clone a http url that ends with the "/.git/"
|
||||||
directory. For example, for downloads.kitenet.net, the clone url
|
directory. For example, for downloads.kitenet.net, the clone url
|
||||||
is `https://downloads.kitenet.net/.git/`
|
is `https://downloads.kitenet.net/.git/`
|
||||||
8. Set up a git `post-receive` hook to update the repository's working tree
|
9. Set up a git `post-receive` hook to update the repository's working tree
|
||||||
when changes are pushed to it. See below for details.
|
when changes are pushed to it. See below for details.
|
||||||
|
|
||||||
When users clone over http, and run git-annex, it will
|
When users clone over http, and run git-annex, it will
|
||||||
|
|
|
@ -0,0 +1,8 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="https://me.yahoo.com/a/2grhJvAC049fJnvALDXek.6MRZMTlg--#eec89"
|
||||||
|
nickname="John"
|
||||||
|
subject="comment 2"
|
||||||
|
date="2013-08-30T06:09:29Z"
|
||||||
|
content="""
|
||||||
|
You may want to try my `sizes` tool on Hackage. Just pass `-A` and it will be aware of the annex and report sizes as if no files were annexed. The only downside is that it reports file usage for replicated content multiple times, as if you'd copied the data out of the annex rather than hardlinked all duplicate copies (although, this may be exactly the behavior some people want).
|
||||||
|
"""]]
|
|
@ -0,0 +1,13 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="Gastlag"
|
||||||
|
ip="109.190.97.30"
|
||||||
|
subject="Gittorrent"
|
||||||
|
date="2013-08-28T21:49:56Z"
|
||||||
|
content="""
|
||||||
|
May this could interest you : few years ago somes tried to mix Git and Bittorrent.
|
||||||
|
|
||||||
|
http://www.advogato.org/article/994.html
|
||||||
|
http://utsl.gen.nz/gittorrent/rfc.html
|
||||||
|
http://code.google.com/p/gittorrent/
|
||||||
|
https://git.wiki.kernel.org/index.php/SoC2010Application#Did_your_organization_participate_in_past_GSoCs.3F_If_so.2C_please_summarize_your_involvement_and_the_successes_and_challenges_of_your_participation
|
||||||
|
"""]]
|
|
@ -6,7 +6,7 @@ We can use this to copy everything in the laptop's annex to the
|
||||||
USB drive.
|
USB drive.
|
||||||
|
|
||||||
# cd /media/usb/annex
|
# cd /media/usb/annex
|
||||||
# git fetch laptop; git merge laptop/master
|
# git annex sync laptop
|
||||||
# git annex get .
|
# git annex get .
|
||||||
get my_cool_big_file (from laptop...) ok
|
get my_cool_big_file (from laptop...) ok
|
||||||
get iso/debian.iso (from laptop...) ok
|
get iso/debian.iso (from laptop...) ok
|
||||||
|
|
Loading…
Add table
Reference in a new issue