refactoring, no code changes really

This commit is contained in:
Joey Hess 2010-11-08 15:15:21 -04:00
parent 02a21d7f27
commit 070e8530c1
19 changed files with 105 additions and 74 deletions

View file

@ -31,13 +31,13 @@ import Control.Monad.State
import IO (try) import IO (try)
import System.FilePath import System.FilePath
import System.Posix.Files import System.Posix.Files
import Core
import Locations import Locations
import qualified GitRepo as Git import qualified GitRepo as Git
import qualified Annex import qualified Annex
import Types import Types
import qualified TypeInternals as Internals import qualified TypeInternals as Internals
import Messages
{- List of backends in the order to try them when storing a new key. -} {- List of backends in the order to try them when storing a new key. -}
list :: Annex [Backend] list :: Annex [Backend]

View file

@ -25,6 +25,7 @@ import qualified GitRepo as Git
import Core import Core
import qualified Annex import qualified Annex
import UUID import UUID
import Messages
backend :: Backend backend :: Backend
backend = Backend { backend = Backend {

View file

@ -14,7 +14,7 @@ import System.IO
import qualified Backend.File import qualified Backend.File
import TypeInternals import TypeInternals
import Core import Messages
backend :: Backend backend :: Backend
backend = Backend.File.backend { backend = Backend.File.backend {

View file

@ -11,8 +11,8 @@ import Control.Monad.State (liftIO)
import Data.String.Utils import Data.String.Utils
import TypeInternals import TypeInternals
import Core
import Utility import Utility
import Messages
backend :: Backend backend :: Backend
backend = Backend { backend = Backend {

View file

@ -9,7 +9,7 @@ module Command where
import Types import Types
import qualified Backend import qualified Backend
import Core import Messages
import qualified Annex import qualified Annex
{- A subcommand runs in four stages. {- A subcommand runs in four stages.

View file

@ -19,6 +19,7 @@ import qualified Backend
import LocationLog import LocationLog
import Types import Types
import Core import Core
import Messages
{- The add subcommand annexes a file, storing it in a backend, and then {- The add subcommand annexes a file, storing it in a backend, and then
- moving it into the annex directory and setting up the symlink pointing - moving it into the annex directory and setting up the symlink pointing

View file

@ -17,6 +17,7 @@ import qualified Backend
import LocationLog import LocationLog
import Types import Types
import Core import Core
import Messages
{- Indicates a file's content is not wanted anymore, and should be removed {- Indicates a file's content is not wanted anymore, and should be removed
- if it's safe to do so. -} - if it's safe to do so. -}

View file

@ -17,6 +17,7 @@ import qualified Backend
import LocationLog import LocationLog
import Types import Types
import Core import Core
import Messages
{- Drops cached content for a key. -} {- Drops cached content for a key. -}
start :: SubCmdStartString start :: SubCmdStartString

View file

@ -15,6 +15,7 @@ import Command
import qualified Annex import qualified Annex
import Utility import Utility
import Core import Core
import Messages
{- Fixes the symlink to an annexed file. -} {- Fixes the symlink to an annexed file. -}
start :: SubCmdStartString start :: SubCmdStartString

View file

@ -18,6 +18,7 @@ import Utility
import qualified Backend import qualified Backend
import Types import Types
import Core import Core
import Messages
{- Adds a file pointing at a manually-specified key -} {- Adds a file pointing at a manually-specified key -}
start :: SubCmdStartString start :: SubCmdStartString

View file

@ -8,19 +8,11 @@
module Command.Fsck where module Command.Fsck where
import qualified Data.Map as M import qualified Data.Map as M
import System.Directory
import System.Posix.Files
import Monad (filterM)
import Control.Monad.State (liftIO)
import Data.Maybe
import Command import Command
import Types import Types
import Core import Core
import Locations import Messages
import qualified Annex
import qualified GitRepo as Git
import qualified Backend
{- Checks the whole annex for problems. -} {- Checks the whole annex for problems. -}
start :: SubCmdStart start :: SubCmdStart
@ -71,22 +63,3 @@ unusedKeys = do
existsMap :: Ord k => [k] -> M.Map k Int existsMap :: Ord k => [k] -> M.Map k Int
existsMap l = M.fromList $ map (\k -> (k, 1)) l existsMap l = M.fromList $ map (\k -> (k, 1)) l
getKeysPresent :: Annex [Key]
getKeysPresent = do
g <- Annex.gitRepo
let top = annexDir g
contents <- liftIO $ getDirectoryContents top
files <- liftIO $ filterM (isreg top) contents
return $ map fileKey files
where
isreg top f = do
s <- getFileStatus $ top ++ "/" ++ f
return $ isRegularFile s
getKeysReferenced :: Annex [Key]
getKeysReferenced = do
g <- Annex.gitRepo
files <- liftIO $ Git.inRepo g $ Git.workTree g
keypairs <- mapM Backend.lookupFile files
return $ map fst $ catMaybes keypairs

View file

@ -11,6 +11,7 @@ import Command
import qualified Backend import qualified Backend
import Types import Types
import Core import Core
import Messages
{- Gets an annexed file from one of the backends. -} {- Gets an annexed file from one of the backends. -}
start :: SubCmdStartString start :: SubCmdStartString

View file

@ -15,6 +15,7 @@ import qualified Annex
import Core import Core
import qualified GitRepo as Git import qualified GitRepo as Git
import UUID import UUID
import Messages
{- Stores description for the repository etc. -} {- Stores description for the repository etc. -}
start :: SubCmdStartString start :: SubCmdStartString

View file

@ -20,6 +20,7 @@ import Core
import qualified GitRepo as Git import qualified GitRepo as Git
import qualified Remotes import qualified Remotes
import UUID import UUID
import Messages
{- Move a file either --to or --from a repository. {- Move a file either --to or --from a repository.
- -
@ -64,7 +65,7 @@ moveToPerform key = do
showNote $ show err showNote $ show err
return Nothing return Nothing
Right False -> do Right False -> do
Core.showNote $ "moving to " ++ (Git.repoDescribe remote) ++ "..." showNote $ "moving to " ++ (Git.repoDescribe remote) ++ "..."
let tmpfile = (annexTmpLocation remote) ++ (keyFile key) let tmpfile = (annexTmpLocation remote) ++ (keyFile key)
ok <- Remotes.copyToRemote remote key tmpfile ok <- Remotes.copyToRemote remote key tmpfile
if (ok) if (ok)
@ -112,7 +113,7 @@ moveFromPerform key = do
if (ishere) if (ishere)
then return $ Just $ moveFromCleanup remote key then return $ Just $ moveFromCleanup remote key
else do else do
Core.showNote $ "moving from " ++ (Git.repoDescribe remote) ++ "..." showNote $ "moving from " ++ (Git.repoDescribe remote) ++ "..."
ok <- getViaTmp key (Remotes.copyFromRemote remote key) ok <- getViaTmp key (Remotes.copyFromRemote remote key)
if (ok) if (ok)
then return $ Just $ moveFromCleanup remote key then return $ Just $ moveFromCleanup remote key

View file

@ -18,6 +18,7 @@ import qualified Backend
import LocationLog import LocationLog
import Types import Types
import Core import Core
import Messages
{- Sets cached content for a key. -} {- Sets cached content for a key. -}
start :: SubCmdStartString start :: SubCmdStartString

View file

@ -19,6 +19,7 @@ import LocationLog
import Types import Types
import Core import Core
import qualified GitRepo as Git import qualified GitRepo as Git
import Messages
{- The unannex subcommand undoes an add. -} {- The unannex subcommand undoes an add. -}
start :: SubCmdStartString start :: SubCmdStartString

66
Core.hs
View file

@ -8,12 +8,12 @@
module Core where module Core where
import IO (try) import IO (try)
import System.IO
import System.Directory import System.Directory
import Control.Monad.State (liftIO) import Control.Monad.State (liftIO)
import System.Path import System.Path
import Data.String.Utils import Control.Monad (when, unless, filterM)
import Control.Monad (when, unless) import System.Posix.Files
import Data.Maybe
import Types import Types
import Locations import Locations
@ -22,7 +22,9 @@ import UUID
import qualified GitRepo as Git import qualified GitRepo as Git
import qualified GitQueue import qualified GitQueue
import qualified Annex import qualified Annex
import qualified Backend
import Utility import Utility
import Messages
{- Runs a list of Annex actions. Catches IO errors and continues {- Runs a list of Annex actions. Catches IO errors and continues
- (but explicitly thrown errors terminate the whole command). - (but explicitly thrown errors terminate the whole command).
@ -152,6 +154,27 @@ getViaTmp key action = do
-- to resume its transfer -- to resume its transfer
return False return False
{- List of keys whose content exists in .git/annex/objects/ -}
getKeysPresent :: Annex [Key]
getKeysPresent = do
g <- Annex.gitRepo
let top = annexObjectDir g
contents <- liftIO $ getDirectoryContents top
files <- liftIO $ filterM (isreg top) contents
return $ map fileKey files
where
isreg top f = do
s <- getFileStatus $ top ++ "/" ++ f
return $ isRegularFile s
{- List of keys referenced by symlinks in the git repo. -}
getKeysReferenced :: Annex [Key]
getKeysReferenced = do
g <- Annex.gitRepo
files <- liftIO $ Git.inRepo g $ Git.workTree g
keypairs <- mapM Backend.lookupFile files
return $ map fst $ catMaybes keypairs
{- Uses the annex.version git config setting to automate upgrades. -} {- Uses the annex.version git config setting to automate upgrades. -}
autoUpgrade :: Annex () autoUpgrade :: Annex ()
autoUpgrade = do autoUpgrade = do
@ -159,6 +182,8 @@ autoUpgrade = do
case Git.configGet g field "0" of case Git.configGet g field "0" of
"0" -> do -- before there was repo versioning "0" -> do -- before there was repo versioning
upgradeNote "Upgrading object directory layout..."
setVersion setVersion
v | v == currentVersion -> return () v | v == currentVersion -> return ()
_ -> error "this version of git-annex is too old for this git repository!" _ -> error "this version of git-annex is too old for this git repository!"
@ -166,37 +191,4 @@ autoUpgrade = do
currentVersion = "1" currentVersion = "1"
setVersion = Annex.setConfig field currentVersion setVersion = Annex.setConfig field currentVersion
field = "annex.version" field = "annex.version"
upgradeNote s = verbose $ liftIO $ putStrLn $ "("++s++")"
{- Output logging -}
verbose :: Annex () -> Annex ()
verbose a = do
q <- Annex.flagIsSet "quiet"
unless q a
showStart :: String -> String -> Annex ()
showStart command file = verbose $ do
liftIO $ putStr $ command ++ " " ++ file ++ " "
liftIO $ hFlush stdout
showNote :: String -> Annex ()
showNote s = verbose $ do
liftIO $ putStr $ "(" ++ s ++ ") "
liftIO $ hFlush stdout
showProgress :: Annex ()
showProgress = verbose $ liftIO $ putStr "\n"
showLongNote :: String -> Annex ()
showLongNote s = verbose $ do
liftIO $ putStr $ "\n" ++ indented
where
indented = join "\n" $ map (\l -> " " ++ l) $ lines s
showEndOk :: Annex ()
showEndOk = verbose $ do
liftIO $ putStrLn "ok"
showEndFail :: Annex ()
showEndFail = verbose $ do
liftIO $ putStrLn "\nfailed"
{- Exception pretty-printing. -}
showErr :: (Show a) => a -> Annex ()
showErr e = warning $ show e
warning :: String -> Annex ()
warning s = liftIO $ hPutStrLn stderr $ "git-annex: " ++ s

54
Messages.hs Normal file
View file

@ -0,0 +1,54 @@
{- git-annex output messages
-
- Copyright 2010 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Messages where
import Control.Monad.State (liftIO)
import System.IO
import Control.Monad (unless)
import Data.String.Utils
import Types
import qualified Annex
verbose :: Annex () -> Annex ()
verbose a = do
q <- Annex.flagIsSet "quiet"
unless q a
showStart :: String -> String -> Annex ()
showStart command file = verbose $ do
liftIO $ putStr $ command ++ " " ++ file ++ " "
liftIO $ hFlush stdout
showNote :: String -> Annex ()
showNote s = verbose $ do
liftIO $ putStr $ "(" ++ s ++ ") "
liftIO $ hFlush stdout
showProgress :: Annex ()
showProgress = verbose $ liftIO $ putStr "\n"
showLongNote :: String -> Annex ()
showLongNote s = verbose $ do
liftIO $ putStr $ "\n" ++ indented
where
indented = join "\n" $ map (\l -> " " ++ l) $ lines s
showEndOk :: Annex ()
showEndOk = verbose $ do
liftIO $ putStrLn "ok"
showEndFail :: Annex ()
showEndFail = verbose $ do
liftIO $ putStrLn "\nfailed"
{- Exception pretty-printing. -}
showErr :: (Show a) => a -> Annex ()
showErr e = warning $ show e
warning :: String -> Annex ()
warning s = liftIO $ hPutStrLn stderr $ "git-annex: " ++ s

View file

@ -36,6 +36,7 @@ import Locations
import UUID import UUID
import Utility import Utility
import qualified Core import qualified Core
import Messages
{- Human visible list of remotes. -} {- Human visible list of remotes. -}
list :: [Git.Repo] -> String list :: [Git.Repo] -> String
@ -64,7 +65,7 @@ keyPossibilities key = do
let expensive = filter Git.repoIsUrl allremotes let expensive = filter Git.repoIsUrl allremotes
doexpensive <- filterM cachedUUID expensive doexpensive <- filterM cachedUUID expensive
unless (null doexpensive) $ do unless (null doexpensive) $ do
Core.showNote $ "getting UUID for " ++ showNote $ "getting UUID for " ++
(list doexpensive) ++ "..." (list doexpensive) ++ "..."
let todo = cheap ++ doexpensive let todo = cheap ++ doexpensive
if (not $ null todo) if (not $ null todo)
@ -93,7 +94,7 @@ inAnnex r key = do
a <- Annex.new r [] a <- Annex.new r []
Annex.eval a (Core.inAnnex key) Annex.eval a (Core.inAnnex key)
checkremote = do checkremote = do
Core.showNote ("checking " ++ Git.repoDescribe r ++ "...") showNote ("checking " ++ Git.repoDescribe r ++ "...")
inannex <- runCmd r "test" ["-e", annexLocation r key] inannex <- runCmd r "test" ["-e", annexLocation r key]
-- XXX Note that ssh failing and the file not existing -- XXX Note that ssh failing and the file not existing
-- are not currently differentiated. -- are not currently differentiated.
@ -228,7 +229,7 @@ sshLocation r file = (Git.urlHost r) ++ ":" ++ shellEscape file
scp :: Git.Repo -> [String] -> Annex Bool scp :: Git.Repo -> [String] -> Annex Bool
scp r params = do scp r params = do
scpoptions <- repoConfig r "scp-options" "" scpoptions <- repoConfig r "scp-options" ""
Core.showProgress -- make way for scp progress bar showProgress -- make way for scp progress bar
liftIO $ boolSystem "scp" $ "-p":(words scpoptions) ++ params liftIO $ boolSystem "scp" $ "-p":(words scpoptions) ++ params
{- Runs a command in a remote, using ssh if necessary. {- Runs a command in a remote, using ssh if necessary.