factor out common imports

no code changes
This commit is contained in:
Joey Hess 2011-10-03 22:24:57 -04:00
parent 003a604a6e
commit 8ef2095fa0
83 changed files with 264 additions and 619 deletions

View file

@ -7,26 +7,17 @@
module Command.Add where
import Control.Monad.State (liftIO)
import Control.Monad (when)
import System.Posix.Files
import System.Directory
import Control.Exception.Control (handle)
import Control.Exception.Base (throwIO)
import Control.Exception.Extensible (IOException)
import AnnexCommon
import Command
import qualified Annex
import qualified AnnexQueue
import qualified Backend
import LocationLog
import Types
import Content
import Messages
import Utility.Conditional
import Utility.Touch
import Utility.SafeCommand
import Locations
import Backend
command :: [Command]
@ -72,7 +63,7 @@ undo file key e = do
-- fromAnnex could fail if the file ownership is weird
tryharder :: IOException -> Annex ()
tryharder _ = do
g <- Annex.gitRepo
g <- gitRepo
liftIO $ renameFile (gitAnnexLocation g key) file
cleanup :: FilePath -> Key -> Bool -> CommandCleanup

View file

@ -7,12 +7,9 @@
module Command.AddUrl where
import Control.Monad.State
import Network.URI
import Data.String.Utils
import Data.Maybe
import System.Directory
import AnnexCommon
import Command
import qualified Backend
import qualified Utility.Url as Url
@ -20,12 +17,8 @@ import qualified Remote.Web
import qualified Command.Add
import qualified Annex
import qualified Backend.URL
import Messages
import Content
import PresenceLog
import Locations
import Utility.Path
import Utility.Conditional
command :: [Command]
command = [repoCommand "addurl" (paramRepeating paramUrl) seek
@ -51,7 +44,7 @@ perform url file = do
download :: String -> FilePath -> CommandPerform
download url file = do
g <- Annex.gitRepo
g <- gitRepo
showAction $ "downloading " ++ url ++ " "
let dummykey = Backend.URL.fromUrl url
let tmp = gitAnnexTmpLocation g dummykey

View file

@ -7,9 +7,7 @@
module Command.ConfigList where
import Control.Monad.State (liftIO)
import Annex
import AnnexCommon
import Command
import UUID
@ -22,7 +20,7 @@ seek = [withNothing start]
start :: CommandStart
start = do
g <- Annex.gitRepo
g <- gitRepo
u <- getUUID g
liftIO $ putStrLn $ "annex.uuid=" ++ u
stop

View file

@ -7,10 +7,10 @@
module Command.Describe where
import AnnexCommon
import Command
import qualified Remote
import UUID
import Messages
command :: [Command]
command = [repoCommand "describe" (paramPair paramRemote paramDesc) seek

View file

@ -7,14 +7,12 @@
module Command.Drop where
import AnnexCommon
import Command
import qualified Remote
import qualified Annex
import LocationLog
import Types
import Content
import Messages
import Utility.Conditional
import Trust
import Config
@ -71,9 +69,9 @@ dropKey key numcopiesM = do
| length have >= need = return True
| otherwise = do
let u = Remote.uuid r
let dup = u `elem` have
let duplicate = u `elem` have
haskey <- Remote.hasKey r key
case (dup, haskey) of
case (duplicate, haskey) of
(False, Right True) -> findcopies need (u:have) rs bad
(False, Left _) -> findcopies need have rs (r:bad)
_ -> findcopies need have rs bad

View file

@ -7,12 +7,11 @@
module Command.DropKey where
import AnnexCommon
import Command
import qualified Annex
import LocationLog
import Types
import Content
import Messages
command :: [Command]
command = [repoCommand "dropkey" (paramRepeating paramKey) seek

View file

@ -7,22 +7,16 @@
module Command.DropUnused where
import Control.Monad.State (liftIO)
import qualified Data.Map as M
import System.Directory
import Data.Maybe
import AnnexCommon
import Command
import Types
import Messages
import Locations
import qualified Annex
import qualified Command.Drop
import qualified Command.Move
import qualified Remote
import qualified Git
import Types.Key
import Utility.Conditional
type UnusedMap = M.Map String Key
@ -67,14 +61,14 @@ perform key = maybe droplocal dropremote =<< Annex.getState Annex.fromremote
performOther :: (Git.Repo -> Key -> FilePath) -> Key -> CommandPerform
performOther filespec key = do
g <- Annex.gitRepo
g <- gitRepo
let f = filespec g key
liftIO $ whenM (doesFileExist f) $ removeFile f
next $ return True
readUnusedLog :: FilePath -> Annex UnusedMap
readUnusedLog prefix = do
g <- Annex.gitRepo
g <- gitRepo
let f = gitAnnexUnusedLog prefix g
e <- liftIO $ doesFileExist f
if e

View file

@ -7,11 +7,9 @@
module Command.Find where
import Control.Monad.State
import AnnexCommon
import Command
import Content
import Utility.Conditional
import Limit
command :: [Command]

View file

@ -7,16 +7,10 @@
module Command.Fix where
import Control.Monad.State (liftIO)
import System.Posix.Files
import System.Directory
import AnnexCommon
import Command
import qualified AnnexQueue
import Utility.Path
import Utility.SafeCommand
import Content
import Messages
command :: [Command]
command = [repoCommand "fix" paramPaths seek

View file

@ -7,18 +7,11 @@
module Command.FromKey where
import Control.Monad.State (liftIO)
import System.Posix.Files
import System.Directory
import Control.Monad (unless)
import AnnexCommon
import Command
import qualified AnnexQueue
import Utility.SafeCommand
import Content
import Messages
import Types.Key
import Utility.Path
command :: [Command]
command = [repoCommand "fromkey" paramPath seek

View file

@ -7,25 +7,16 @@
module Command.Fsck where
import Control.Monad (when)
import Control.Monad.State (liftIO)
import System.Directory
import System.Posix.Files
import AnnexCommon
import Command
import qualified Annex
import qualified Remote
import qualified Types.Backend
import qualified Types.Key
import UUID
import Types
import Messages
import Content
import LocationLog
import Locations
import Trust
import Utility.DataUnits
import Utility.Path
import Utility.FileMode
import Config
@ -54,7 +45,7 @@ perform key file backend numcopies = do
in this repository only. -}
verifyLocationLog :: Key -> FilePath -> Annex Bool
verifyLocationLog key file = do
g <- Annex.gitRepo
g <- gitRepo
present <- inAnnex key
-- Since we're checking that a key's file is present, throw
@ -98,7 +89,7 @@ fsckKey backend key file numcopies = do
- the key's metadata, if available. -}
checkKeySize :: Key -> Annex Bool
checkKeySize key = do
g <- Annex.gitRepo
g <- gitRepo
let file = gitAnnexLocation g key
present <- liftIO $ doesFileExist file
case (present, Types.Key.keySize key) of

View file

@ -7,12 +7,11 @@
module Command.Get where
import AnnexCommon
import Command
import qualified Annex
import qualified Remote
import Types
import Content
import Messages
import qualified Command.Move
command :: [Command]

View file

@ -7,12 +7,9 @@
module Command.InAnnex where
import Control.Monad.State (liftIO)
import System.Exit
import AnnexCommon
import Command
import Content
import Types
command :: [Command]
command = [repoCommand "inannex" (paramRepeating paramKey) seek

View file

@ -7,10 +7,9 @@
module Command.Init where
import AnnexCommon
import Command
import qualified Annex
import UUID
import Messages
import Init
command :: [Command]
@ -30,7 +29,7 @@ start ws = do
perform :: String -> CommandPerform
perform description = do
initialize
g <- Annex.gitRepo
g <- gitRepo
u <- getUUID g
describeUUID u description
next $ return True

View file

@ -8,18 +8,13 @@
module Command.InitRemote where
import qualified Data.Map as M
import Control.Monad (when)
import Control.Monad.State (liftIO)
import Data.Maybe
import Data.String.Utils
import AnnexCommon
import Command
import qualified Remote
import qualified RemoteLog
import qualified Types.Remote as R
import Types
import UUID
import Messages
command :: [Command]
command = [repoCommand "initremote"

View file

@ -7,13 +7,9 @@
module Command.Lock where
import Control.Monad.State (liftIO)
import System.Directory
import AnnexCommon
import Command
import Messages
import qualified AnnexQueue
import Utility.SafeCommand
import Backend
command :: [Command]

View file

@ -7,19 +7,12 @@
module Command.Map where
import Control.Monad.State (liftIO)
import Control.Exception.Extensible
import System.Cmd.Utils
import qualified Data.Map as M
import Data.List.Utils
import Data.Maybe
import AnnexCommon
import Command
import qualified Annex
import qualified Git
import Messages
import Types
import Utility.SafeCommand
import UUID
import Trust
import Utility.Ssh
@ -36,7 +29,7 @@ seek = [withNothing start]
start :: CommandStart
start = do
g <- Annex.gitRepo
g <- gitRepo
rs <- spider g
umap <- uuidMap

View file

@ -7,9 +7,9 @@
module Command.Merge where
import AnnexCommon
import Command
import qualified Branch
import Messages
command :: [Command]
command = [repoCommand "merge" paramNothing seek

View file

@ -7,22 +7,11 @@
module Command.Migrate where
import Control.Monad.State (liftIO)
import Control.Applicative
import System.Posix.Files
import System.Directory
import System.FilePath
import Data.Maybe
import AnnexCommon
import Command
import qualified Annex
import qualified Backend
import qualified Types.Key
import Locations
import Types
import Content
import Messages
import Utility.Conditional
import qualified Command.Add
import Backend
@ -53,7 +42,7 @@ upgradableKey key = isNothing $ Types.Key.keySize key
perform :: FilePath -> Key -> Backend Annex -> CommandPerform
perform file oldkey newbackend = do
g <- Annex.gitRepo
g <- gitRepo
-- Store the old backend's cached key in the new backend
-- (the file can't be stored as usual, because it's already a symlink).

View file

@ -7,18 +7,14 @@
module Command.Move where
import Control.Monad (when)
import AnnexCommon
import Command
import qualified Command.Drop
import qualified Annex
import LocationLog
import Types
import Content
import qualified Remote
import UUID
import Messages
import Utility.Conditional
command :: [Command]
command = [repoCommand "move" paramPaths seek
@ -60,7 +56,7 @@ showMoveAction False file = showStart "copy" file
remoteHasKey :: Remote.Remote Annex -> Key -> Bool -> Annex ()
remoteHasKey remote key present = do
let remoteuuid = Remote.uuid remote
g <- Annex.gitRepo
g <- gitRepo
logChange g key remoteuuid status
where
status = if present then InfoPresent else InfoMissing
@ -76,7 +72,7 @@ remoteHasKey remote key present = do
-}
toStart :: Remote.Remote Annex -> Bool -> FilePath -> CommandStart
toStart dest move file = isAnnexed file $ \(key, _) -> do
g <- Annex.gitRepo
g <- gitRepo
u <- getUUID g
ishere <- inAnnex key
if not ishere || u == Remote.uuid dest
@ -126,7 +122,7 @@ toCleanup dest move key = do
-}
fromStart :: Remote.Remote Annex -> Bool -> FilePath -> CommandStart
fromStart src move file = isAnnexed file $ \(key, _) -> do
g <- Annex.gitRepo
g <- gitRepo
u <- getUUID g
remotes <- Remote.keyPossibilities key
if u == Remote.uuid src || not (any (== src) remotes)

View file

@ -7,15 +7,11 @@
module Command.RecvKey where
import Control.Monad.State (liftIO)
import System.Exit
import AnnexCommon
import Command
import CmdLine
import Content
import Utility.RsyncFile
import Utility.Conditional
import Types
command :: [Command]
command = [repoCommand "recvkey" paramKey seek

View file

@ -7,11 +7,11 @@
module Command.Semitrust where
import AnnexCommon
import Command
import qualified Remote
import UUID
import Trust
import Messages
command :: [Command]
command = [repoCommand "semitrust" (paramRepeating paramRemote) seek

View file

@ -7,17 +7,10 @@
module Command.SendKey where
import Control.Monad.State (liftIO)
import System.Exit
import Locations
import qualified Annex
import AnnexCommon
import Command
import Content
import Utility.RsyncFile
import Utility.Conditional
import Messages
import Types
command :: [Command]
command = [repoCommand "sendkey" paramKey seek
@ -28,7 +21,7 @@ seek = [withKeys start]
start :: Key -> CommandStart
start key = do
g <- Annex.gitRepo
g <- gitRepo
let file = gitAnnexLocation g key
whenM (inAnnex key) $
liftIO $ rsyncServerSend file -- does not return

View file

@ -7,13 +7,10 @@
module Command.SetKey where
import Control.Monad.State (liftIO)
import AnnexCommon
import Command
import Utility.SafeCommand
import LocationLog
import Content
import Messages
command :: [Command]
command = [repoCommand "setkey" paramPath seek

View file

@ -8,25 +8,20 @@
module Command.Status where
import Control.Monad.State
import Control.Applicative
import Data.Maybe
import System.IO
import Data.List
import qualified Data.Map as M
import qualified Data.Set as S
import Data.Set (Set)
import AnnexCommon
import qualified Types.Backend as B
import qualified Types.Remote as R
import qualified Remote
import qualified Command.Unused
import qualified Git
import Command
import Types
import Utility.DataUnits
import Content
import Types.Key
import Locations
import Backend
import UUID
import Remote

View file

@ -7,11 +7,11 @@
module Command.Trust where
import AnnexCommon
import Command
import qualified Remote
import Trust
import UUID
import Messages
command :: [Command]
command = [repoCommand "trust" (paramRepeating paramRemote) seek

View file

@ -7,25 +7,16 @@
module Command.Unannex where
import Control.Monad.State (liftIO)
import Control.Monad (unless)
import System.Directory
import System.Posix.Files
import AnnexCommon
import Command
import qualified Command.Drop
import qualified Annex
import qualified AnnexQueue
import Utility.SafeCommand
import Utility.Path
import Utility.FileMode
import LocationLog
import Types
import Content
import qualified Git
import qualified Git.LsFiles as LsFiles
import Messages
import Locations
command :: [Command]
command = [repoCommand "unannex" paramPaths seek "undo accidential add command"]
@ -41,7 +32,7 @@ start file = isAnnexed file $ \(key, _) -> do
then do
force <- Annex.getState Annex.force
unless force $ do
g <- Annex.gitRepo
g <- gitRepo
staged <- liftIO $ LsFiles.staged g [Git.workTree g]
unless (null staged) $
error "This command cannot be run when there are already files staged for commit."
@ -60,7 +51,7 @@ perform file key = do
cleanup :: FilePath -> Key -> CommandCleanup
cleanup file key = do
g <- Annex.gitRepo
g <- gitRepo
liftIO $ removeFile file
liftIO $ Git.run g "rm" [Params "--quiet --", File file]

View file

@ -7,19 +7,14 @@
module Command.Uninit where
import Control.Monad.State (liftIO)
import System.Directory
import System.Exit
import AnnexCommon
import Command
import Utility.SafeCommand
import qualified Git
import qualified Annex
import qualified Command.Unannex
import Init
import qualified Branch
import Content
import Locations
command :: [Command]
command = [repoCommand "uninit" paramPaths seek
@ -44,7 +39,7 @@ perform = next cleanup
cleanup :: CommandCleanup
cleanup = do
g <- Annex.gitRepo
g <- gitRepo
uninitialize
mapM_ removeAnnex =<< getKeysPresent
liftIO $ removeDirectoryRecursive (gitAnnexDir g)

View file

@ -7,18 +7,10 @@
module Command.Unlock where
import Control.Monad.State (liftIO)
import System.Directory hiding (copyFile)
import AnnexCommon
import Command
import qualified Annex
import Types
import Messages
import Locations
import Content
import Utility.Conditional
import Utility.CopyFile
import Utility.Path
import Utility.FileMode
command :: [Command]
@ -43,12 +35,12 @@ perform dest key = do
checkDiskSpace key
g <- Annex.gitRepo
g <- gitRepo
let src = gitAnnexLocation g key
let tmpdest = gitAnnexTmpLocation g key
liftIO $ createDirectoryIfMissing True (parentDir tmpdest)
showAction "copying"
ok <- liftIO $ copyFile src tmpdest
ok <- liftIO $ copyFileExternal src tmpdest
if ok
then do
liftIO $ do

View file

@ -7,11 +7,11 @@
module Command.Untrust where
import AnnexCommon
import Command
import qualified Remote
import UUID
import Trust
import Messages
command :: [Command]
command = [repoCommand "untrust" (paramRepeating paramRemote) seek

View file

@ -9,23 +9,13 @@
module Command.Unused where
import Control.Monad (filterM, unless, forM_)
import Control.Monad.State (liftIO)
import qualified Data.Set as S
import Data.Maybe
import System.FilePath
import System.Directory
import Data.List
import qualified Data.ByteString.Lazy.Char8 as L
import AnnexCommon
import Command
import Types
import Content
import Messages
import Locations
import Utility
import Utility.FileMode
import Utility.SafeCommand
import LocationLog
import qualified Annex
import qualified Git
@ -92,7 +82,7 @@ checkRemoteUnused' r = do
writeUnusedFile :: FilePath -> [(Int, Key)] -> Annex ()
writeUnusedFile prefix l = do
g <- Annex.gitRepo
g <- gitRepo
liftIO $ viaTmp writeFile (gitAnnexUnusedLog prefix g) $
unlines $ map (\(n, k) -> show n ++ " " ++ show k) l
@ -164,7 +154,7 @@ unusedKeys = do
excludeReferenced :: [Key] -> Annex [Key]
excludeReferenced [] = return [] -- optimisation
excludeReferenced l = do
g <- Annex.gitRepo
g <- gitRepo
c <- liftIO $ Git.pipeRead g [Param "show-ref"]
removewith (getKeysReferenced : map getKeysReferencedInGit (refs c))
(S.fromList l)
@ -200,7 +190,7 @@ exclude smaller larger = S.toList $ remove larger $ S.fromList smaller
{- List of keys referenced by symlinks in the git repo. -}
getKeysReferenced :: Annex [Key]
getKeysReferenced = do
g <- Annex.gitRepo
g <- gitRepo
files <- liftIO $ LsFiles.inRepo g [Git.workTree g]
keypairs <- mapM Backend.lookupFile files
return $ map fst $ catMaybes keypairs
@ -209,7 +199,7 @@ getKeysReferenced = do
getKeysReferencedInGit :: String -> Annex [Key]
getKeysReferencedInGit ref = do
showAction $ "checking " ++ Git.refDescribe ref
g <- Annex.gitRepo
g <- gitRepo
findkeys [] =<< liftIO (LsTree.lsTree g ref)
where
findkeys c [] = return c
@ -232,17 +222,17 @@ staleKeysPrune dirspec present = do
contents <- staleKeys dirspec
let stale = contents `exclude` present
let dup = contents `exclude` stale
let dups = contents `exclude` stale
g <- Annex.gitRepo
g <- gitRepo
let dir = dirspec g
liftIO $ forM_ dup $ \t -> removeFile $ dir </> keyFile t
liftIO $ forM_ dups $ \t -> removeFile $ dir </> keyFile t
return stale
staleKeys :: (Git.Repo -> FilePath) -> Annex [Key]
staleKeys dirspec = do
g <- Annex.gitRepo
g <- gitRepo
let dir = dirspec g
exists <- liftIO $ doesDirectoryExist dir
if not exists

View file

@ -7,10 +7,10 @@
module Command.Upgrade where
import AnnexCommon
import Command
import Upgrade
import Version
import Messages
command :: [Command]
command = [standaloneCommand "upgrade" paramNothing seek

View file

@ -7,10 +7,7 @@
module Command.Version where
import Control.Monad.State (liftIO)
import Data.String.Utils
import Data.Maybe
import AnnexCommon
import Command
import qualified Build.SysConfig as SysConfig
import Version

View file

@ -7,13 +7,10 @@
module Command.Whereis where
import Control.Monad
import AnnexCommon
import LocationLog
import Command
import Messages
import Remote
import Types
import Trust
command :: [Command]