summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Annex/Branch.hs1
-rw-r--r--Command/Forget.hs41
-rw-r--r--GitAnnex.hs2
-rw-r--r--Logs/Transitions.hs10
-rw-r--r--doc/git-annex.mdwn2
5 files changed, 51 insertions, 5 deletions
diff --git a/Annex/Branch.hs b/Annex/Branch.hs
index fa4b0265d..5af6b6be9 100644
--- a/Annex/Branch.hs
+++ b/Annex/Branch.hs
@@ -402,6 +402,7 @@ handleTransitions :: Transitions -> [Git.Ref] -> Annex (Maybe (Git.Branch, [Git.
handleTransitions localts refs = do
m <- M.fromList <$> mapM getreftransition refs
let remotets = M.elems m
+ liftIO $ print ("transitions", localts, remotets)
if all (localts ==) remotets
then return Nothing
else do
diff --git a/Command/Forget.hs b/Command/Forget.hs
new file mode 100644
index 000000000..e405a9918
--- /dev/null
+++ b/Command/Forget.hs
@@ -0,0 +1,41 @@
+{- 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 Data.Time.Clock.POSIX
+
+def :: [Command]
+def = [command "forget" paramNothing seek
+ SectionMaintenance "prune git-annex branch history"]
+
+seek :: [CommandSeek]
+seek = [withNothing start]
+
+start :: CommandStart
+start = do
+ showStart "forget" "git-annex"
+ next $ perform =<< Annex.getState Annex.force
+
+perform :: Bool -> CommandPerform
+perform True = do
+ now <- liftIO getPOSIXTime
+ let ts = addTransition now ForgetGitHistory noTransitions
+ 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
diff --git a/GitAnnex.hs b/GitAnnex.hs
index 05565e643..1212edf9f 100644
--- a/GitAnnex.hs
+++ b/GitAnnex.hs
@@ -67,6 +67,7 @@ import qualified Command.Map
import qualified Command.Direct
import qualified Command.Indirect
import qualified Command.Upgrade
+import qualified Command.Forget
import qualified Command.Version
import qualified Command.Help
#ifdef WITH_ASSISTANT
@@ -139,6 +140,7 @@ cmds = concat
, Command.Direct.def
, Command.Indirect.def
, Command.Upgrade.def
+ , Command.Forget.def
, Command.Version.def
, Command.Help.def
#ifdef WITH_ASSISTANT
diff --git a/Logs/Transitions.hs b/Logs/Transitions.hs
index 41f4b2635..d4b7d5eb3 100644
--- a/Logs/Transitions.hs
+++ b/Logs/Transitions.hs
@@ -50,6 +50,9 @@ 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
@@ -91,8 +94,7 @@ 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. -}
-recordTransition :: (FilePath -> (String -> String) -> Annex ()) -> Transition -> Annex ()
-recordTransition changer o = do
- t <- liftIO getPOSIXTime
+recordTransitions :: (FilePath -> (String -> String) -> Annex ()) -> Transitions -> Annex ()
+recordTransitions changer t = do
changer transitionsLog $
- showTransitions . addTransition t o . parseTransitionsStrictly "local"
+ showTransitions . S.union t . parseTransitionsStrictly "local"
diff --git a/doc/git-annex.mdwn b/doc/git-annex.mdwn
index 72e376d64..5fb0ce5a4 100644
--- a/doc/git-annex.mdwn
+++ b/doc/git-annex.mdwn
@@ -488,7 +488,7 @@ subdirectories).
be located.
To also prune references to remotes that have been marked as dead,
- specify --forget-dead.
+ specify --dead.
When this rewritten branch is merged into other clones of
the repository, git-annex will automatically perform the same rewriting