git-annex/Command.hs

177 lines
5.8 KiB
Haskell
Raw Normal View History

2010-11-11 22:54:52 +00:00
{- git-annex commands
-
- Copyright 2010 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Command where
2010-11-11 22:54:52 +00:00
import Control.Monad.State (liftIO)
import System.Directory
import System.Posix.Files
import Control.Monad (filterM)
import Types
2010-11-04 17:28:49 +00:00
import qualified Backend
2010-11-08 19:15:21 +00:00
import Messages
2010-11-04 17:28:49 +00:00
import qualified Annex
2010-11-11 22:54:52 +00:00
import qualified GitRepo as Git
import Locations
{- A subcommand runs in four stages.
-
- 0. The seek stage takes the parameters passed to the subcommand,
- looks through the repo to find the ones that are relevant
- to that subcommand (ie, new files to add), and generates
- a list of start stage actions. -}
type SubCmdSeek = [String] -> Annex [SubCmdStart]
{- 1. The start stage is run before anything is printed about the
- subcommand, is passed some input, and can early abort it
- if the input does not make sense. It should run quickly and
- should not modify Annex state. -}
type SubCmdStart = Annex (Maybe SubCmdPerform)
{- 2. The perform stage is run after a message is printed about the subcommand
- being run, and it should be where the bulk of the work happens. -}
type SubCmdPerform = Annex (Maybe SubCmdCleanup)
{- 3. The cleanup stage is run only if the perform stage succeeds, and it
- returns the overall success/fail of the subcommand. -}
type SubCmdCleanup = Annex Bool
{- Some helper functions are used to build up SubCmdSeek and SubCmdStart
- functions. -}
type SubCmdSeekStrings = SubCmdStartString -> SubCmdSeek
type SubCmdStartString = String -> SubCmdStart
type SubCmdSeekBackendFiles = SubCmdStartBackendFile -> SubCmdSeek
type SubCmdStartBackendFile = (FilePath, Maybe Backend) -> SubCmdStart
type SubCmdSeekNothing = SubCmdStart -> SubCmdSeek
2010-11-13 20:15:45 +00:00
type SubCmdStartNothing = SubCmdStart
2010-11-04 17:28:49 +00:00
data SubCommand = SubCommand {
subcmdname :: String,
subcmdparams :: String,
subcmdseek :: [SubCmdSeek],
2010-11-04 17:28:49 +00:00
subcmddesc :: String
}
{- Prepares a list of actions to run to perform a subcommand, based on
- the parameters passed to it. -}
prepSubCmd :: SubCommand -> AnnexState -> [String] -> IO [Annex Bool]
prepSubCmd SubCommand { subcmdseek = seek } state params = do
lists <- Annex.eval state $ mapM (\s -> s params) seek
return $ map doSubCmd $ foldl (++) [] lists
2010-11-04 17:28:49 +00:00
{- Runs a subcommand through the start, perform and cleanup stages -}
doSubCmd :: SubCmdStart -> SubCmdCleanup
doSubCmd start = do
s <- start
case (s) of
Nothing -> return True
Just perform -> do
p <- perform
case (p) of
Nothing -> do
showEndFail
return False
Just cleanup -> do
c <- cleanup
if (c)
then do
showEndOk
return True
else do
showEndFail
return False
notAnnexed :: FilePath -> Annex (Maybe a) -> Annex (Maybe a)
notAnnexed file a = do
r <- Backend.lookupFile file
case (r) of
Just _ -> return Nothing
Nothing -> a
isAnnexed :: FilePath -> ((Key, Backend) -> Annex (Maybe a)) -> Annex (Maybe a)
isAnnexed file a = do
r <- Backend.lookupFile file
case (r) of
Just v -> a v
Nothing -> return Nothing
2010-11-11 22:54:52 +00:00
{- These functions find appropriate files or other things based on a
user's parameters, and run a specified action on them. -}
withFilesInGit :: SubCmdSeekStrings
withFilesInGit a params = do
repo <- Annex.gitRepo
files <- liftIO $ mapM (Git.inRepo repo) params
return $ map a $ filter notState $ foldl (++) [] files
withFilesMissing :: SubCmdSeekStrings
withFilesMissing a params = do
files <- liftIO $ filterM missing params
return $ map a $ filter notState files
where
missing f = do
e <- doesFileExist f
return $ not e
withFilesNotInGit :: SubCmdSeekBackendFiles
withFilesNotInGit a params = do
repo <- Annex.gitRepo
newfiles <- liftIO $ mapM (Git.notInRepo repo) params
backendPairs a $ filter notState $ foldl (++) [] newfiles
withFilesUnlocked :: SubCmdSeekBackendFiles
withFilesUnlocked a params = do
-- unlocked files have changed type from a symlink to a regular file
repo <- Annex.gitRepo
typechangedfiles <- liftIO $ mapM (Git.typeChangedFiles repo) params
unlockedfiles <- liftIO $ filterM notSymlink $ foldl (++) [] typechangedfiles
backendPairs a $ filter notState unlockedfiles
backendPairs :: SubCmdSeekBackendFiles
backendPairs a files = do
pairs <- Backend.chooseBackends files
return $ map a pairs
withString :: SubCmdSeekStrings
withString a params = return [a $ unwords params]
2010-11-11 22:54:52 +00:00
withFilesToBeCommitted :: SubCmdSeekStrings
withFilesToBeCommitted a params = do
repo <- Annex.gitRepo
tocommit <- liftIO $ mapM (Git.stagedFiles repo) params
return $ map a $ filter notState $ foldl (++) [] tocommit
withUnlockedFilesToBeCommitted :: SubCmdSeekStrings
withUnlockedFilesToBeCommitted a params = do
repo <- Annex.gitRepo
typechangedfiles <- liftIO $ mapM (Git.typeChangedStagedFiles repo) params
unlockedfiles <- liftIO $ filterM notSymlink $ foldl (++) [] typechangedfiles
return $ map a $ filter notState unlockedfiles
withKeys :: SubCmdSeekStrings
withKeys a params = return $ map a params
withTempFile :: SubCmdSeekStrings
withTempFile a params = return $ map a params
2010-11-13 20:15:45 +00:00
withNothing :: SubCmdSeekNothing
withNothing a [] = return [a]
withNothing _ _ = return []
2010-11-11 22:54:52 +00:00
{- Default to acting on all files matching the seek action if
- none are specified. -}
withAll :: SubCmdSeekStrings -> SubCmdSeekStrings
withAll w a params = do
if null params
then do
g <- Annex.gitRepo
w a [Git.workTree g]
else w a params
2010-11-14 18:58:42 +00:00
{- Provides a default parameter to act on if none is specified. -}
2010-11-14 16:35:05 +00:00
withDefault :: String-> SubCmdSeekStrings -> SubCmdSeekStrings
withDefault d w a params = do
if null params
then w a [d]
else w a params
2010-11-11 22:54:52 +00:00
{- filter out files from the state directory -}
notState :: FilePath -> Bool
notState f = stateLoc /= take (length stateLoc) f
{- filter out symlinks -}
notSymlink :: FilePath -> IO Bool
notSymlink f = do
s <- liftIO $ getSymbolicLinkStatus f
return $ not $ isSymbolicLink s