{- git-annex command - - Copyright 2010 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} module Command.Uninit where import Common.Annex import Command import qualified Git import qualified Annex import qualified Command.Unannex import Init import qualified Annex.Branch import Annex.Content command :: [Command] command = [repoCommand "uninit" paramPaths seek "de-initialize git-annex and clean out repository"] seek :: [CommandSeek] seek = [withFilesInGit startUnannex, withNothing start] startUnannex :: FilePath -> CommandStart startUnannex file = do -- Force fast mode before running unannex. This way, if multiple -- files link to a key, it will be left in the annex and hardlinked -- to by each. Annex.changeState $ \s -> s { Annex.fast = True } Command.Unannex.start file start :: CommandStart start = next perform perform :: CommandPerform perform = next cleanup cleanup :: CommandCleanup cleanup = do g <- gitRepo uninitialize mapM_ removeAnnex =<< getKeysPresent liftIO $ removeDirectoryRecursive (gitAnnexDir g) -- avoid normal shutdown saveState liftIO $ do Git.run g "branch" [Param "-D", Param Annex.Branch.name] exitSuccess