git-annex/Command/Uninit.hs
Joey Hess bf460a0a98 reorder repo parameters last
Many functions took the repo as their first parameter. Changing it
consistently to be the last parameter allows doing some useful things with
currying, that reduce boilerplate.

In particular, g <- gitRepo is almost never needed now, instead
use inRepo to run an IO action in the repo, and fromRepo to get
a value from the repo.

This also provides more opportunities to use monadic and applicative
combinators.
2011-11-08 16:27:20 -04:00

61 lines
1.5 KiB
Haskell

{- git-annex command
-
- Copyright 2010 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Command.Uninit where
import qualified Data.ByteString.Lazy.Char8 as B
import Common.Annex
import Command
import qualified Git
import qualified Annex
import qualified Command.Unannex
import Init
import qualified Annex.Branch
import Annex.Content
def :: [Command]
def = [addCheck check $ command "uninit" paramPaths seek
"de-initialize git-annex and clean out repository"]
check :: Annex ()
check = do
b <- current_branch
when (b == Annex.Branch.name) $ error $
"cannot uninit when the " ++ b ++ " branch is checked out"
where
current_branch = head . lines . B.unpack <$> revhead
revhead = inRepo $ Git.pipeRead
[Params "rev-parse --abbrev-ref HEAD"]
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
annexdir <- fromRepo $ gitAnnexDir
uninitialize
mapM_ removeAnnex =<< getKeysPresent
liftIO $ removeDirectoryRecursive annexdir
-- avoid normal shutdown
saveState
inRepo $ Git.run "branch" [Param "-D", Param Annex.Branch.name]
liftIO $ exitSuccess