This commit is contained in:
Joey Hess 2011-10-04 00:40:47 -04:00
parent ff21fd4a65
commit cfe21e85e7
73 changed files with 173 additions and 173 deletions

View file

@ -5,7 +5,7 @@
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
module Branch ( module Annex.Branch (
create, create,
update, update,
get, get,
@ -22,13 +22,13 @@ import System.IO.Binary
import System.Exit import System.Exit
import qualified Data.ByteString.Lazy.Char8 as L import qualified Data.ByteString.Lazy.Char8 as L
import AnnexCommon import Annex.Common
import Annex.Exception import Annex.Exception
import Types.BranchState import Types.BranchState
import qualified Git import qualified Git
import qualified Git.UnionMerge import qualified Git.UnionMerge
import qualified Annex import qualified Annex
import CatFile import Annex.CatFile
type GitRef = String type GitRef = String

View file

@ -5,11 +5,11 @@
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
module CatFile ( module Annex.CatFile (
catFile catFile
) where ) where
import AnnexCommon import Annex.Common
import qualified Git.CatFile import qualified Git.CatFile
import qualified Annex import qualified Annex

View file

@ -1,4 +1,4 @@
module AnnexCommon ( module Annex.Common (
module Common, module Common,
module Types, module Types,
module Annex, module Annex,

View file

@ -5,7 +5,7 @@
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
module Content ( module Annex.Content (
inAnnex, inAnnex,
calcGitLink, calcGitLink,
logStatus, logStatus,
@ -21,13 +21,13 @@ module Content (
saveState saveState
) where ) where
import AnnexCommon import Annex.Common
import LocationLog import LocationLog
import UUID import UUID
import qualified Git import qualified Git
import qualified Annex import qualified Annex
import qualified AnnexQueue import qualified Annex.Queue
import qualified Branch import qualified Annex.Branch
import Utility.StatFS import Utility.StatFS
import Utility.FileMode import Utility.FileMode
import Types.Key import Types.Key
@ -233,5 +233,5 @@ getKeysPresent' dir = do
{- Things to do to record changes to content. -} {- Things to do to record changes to content. -}
saveState :: Annex () saveState :: Annex ()
saveState = do saveState = do
AnnexQueue.flush False Annex.Queue.flush False
Branch.commit "update" Annex.Branch.commit "update"

View file

@ -15,7 +15,7 @@ import Control.Exception.Control (handle)
import Control.Monad.IO.Control (liftIOOp) import Control.Monad.IO.Control (liftIOOp)
import Control.Exception hiding (handle, throw) import Control.Exception hiding (handle, throw)
import AnnexCommon import Annex.Common
{- Runs an Annex action, with setup and cleanup both in the IO monad. -} {- Runs an Annex action, with setup and cleanup both in the IO monad. -}
bracketIO :: IO c -> (c -> IO b) -> Annex a -> Annex a bracketIO :: IO c -> (c -> IO b) -> Annex a -> Annex a

View file

@ -5,13 +5,13 @@
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
module AnnexQueue ( module Annex.Queue (
add, add,
flush, flush,
flushWhenFull flushWhenFull
) where ) where
import AnnexCommon import Annex.Common
import Annex import Annex
import qualified Git.Queue import qualified Git.Queue

View file

@ -5,9 +5,9 @@
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
module Version where module Annex.Version where
import AnnexCommon import Annex.Common
import qualified Git import qualified Git
import Config import Config

View file

@ -19,7 +19,7 @@ module Backend (
import System.IO.Error (try) import System.IO.Error (try)
import System.Posix.Files import System.Posix.Files
import AnnexCommon import Annex.Common
import qualified Git import qualified Git
import qualified Annex import qualified Annex
import Types.Key import Types.Key

View file

@ -7,9 +7,9 @@
module Backend.SHA (backends) where module Backend.SHA (backends) where
import AnnexCommon import Annex.Common
import qualified Annex import qualified Annex
import Content import Annex.Content
import Types.Backend import Types.Backend
import Types.Key import Types.Key
import qualified Build.SysConfig as SysConfig import qualified Build.SysConfig as SysConfig

View file

@ -10,7 +10,7 @@ module Backend.URL (
fromUrl fromUrl
) where ) where
import AnnexCommon import Annex.Common
import Types.Backend import Types.Backend
import Types.Key import Types.Key

View file

@ -7,7 +7,7 @@
module Backend.WORM (backends) where module Backend.WORM (backends) where
import AnnexCommon import Annex.Common
import Types.Backend import Types.Backend
import Types.Key import Types.Key

View file

@ -14,11 +14,11 @@ module CmdLine (
import System.IO.Error (try) import System.IO.Error (try)
import System.Console.GetOpt import System.Console.GetOpt
import AnnexCommon import Annex.Common
import qualified Annex import qualified Annex
import qualified AnnexQueue import qualified Annex.Queue
import qualified Git import qualified Git
import Content import Annex.Content
import Command import Command
import Options import Options
import Init import Init
@ -81,7 +81,7 @@ tryRun = tryRun' 0
tryRun' :: Integer -> Annex.AnnexState -> [Annex Bool] -> IO () tryRun' :: Integer -> Annex.AnnexState -> [Annex Bool] -> IO ()
tryRun' errnum state (a:as) = do tryRun' errnum state (a:as) = do
result <- try $ Annex.run state $ do result <- try $ Annex.run state $ do
AnnexQueue.flushWhenFull Annex.Queue.flushWhenFull
a a
case result of case result of
Left err -> do Left err -> do

View file

@ -7,7 +7,7 @@
module Command where module Command where
import AnnexCommon import Annex.Common
import qualified Backend import qualified Backend
import qualified Annex import qualified Annex
import qualified Git import qualified Git

View file

@ -7,14 +7,14 @@
module Command.Add where module Command.Add where
import AnnexCommon import Annex.Common
import Annex.Exception import Annex.Exception
import Command import Command
import qualified Annex import qualified Annex
import qualified AnnexQueue import qualified Annex.Queue
import qualified Backend import qualified Backend
import LocationLog import LocationLog
import Content import Annex.Content
import Utility.Touch import Utility.Touch
import Backend import Backend
@ -81,6 +81,6 @@ cleanup file key hascontent = do
force <- Annex.getState Annex.force force <- Annex.getState Annex.force
if force if force
then AnnexQueue.add "add" [Param "-f", Param "--"] [file] then Annex.Queue.add "add" [Param "-f", Param "--"] [file]
else AnnexQueue.add "add" [Param "--"] [file] else Annex.Queue.add "add" [Param "--"] [file]
return True return True

View file

@ -9,7 +9,7 @@ module Command.AddUrl where
import Network.URI import Network.URI
import AnnexCommon import Annex.Common
import Command import Command
import qualified Backend import qualified Backend
import qualified Utility.Url as Url import qualified Utility.Url as Url
@ -17,7 +17,7 @@ import qualified Remote.Web
import qualified Command.Add import qualified Command.Add
import qualified Annex import qualified Annex
import qualified Backend.URL import qualified Backend.URL
import Content import Annex.Content
import PresenceLog import PresenceLog
command :: [Command] command :: [Command]

View file

@ -7,7 +7,7 @@
module Command.ConfigList where module Command.ConfigList where
import AnnexCommon import Annex.Common
import Command import Command
import UUID import UUID

View file

@ -7,7 +7,7 @@
module Command.Describe where module Command.Describe where
import AnnexCommon import Annex.Common
import Command import Command
import qualified Remote import qualified Remote
import UUID import UUID

View file

@ -7,12 +7,12 @@
module Command.Drop where module Command.Drop where
import AnnexCommon import Annex.Common
import Command import Command
import qualified Remote import qualified Remote
import qualified Annex import qualified Annex
import LocationLog import LocationLog
import Content import Annex.Content
import Trust import Trust
import Config import Config

View file

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

View file

@ -9,7 +9,7 @@ module Command.DropUnused where
import qualified Data.Map as M import qualified Data.Map as M
import AnnexCommon import Annex.Common
import Command import Command
import qualified Annex import qualified Annex
import qualified Command.Drop import qualified Command.Drop

View file

@ -7,9 +7,9 @@
module Command.Find where module Command.Find where
import AnnexCommon import Annex.Common
import Command import Command
import Content import Annex.Content
import Limit import Limit
command :: [Command] command :: [Command]

View file

@ -7,10 +7,10 @@
module Command.Fix where module Command.Fix where
import AnnexCommon import Annex.Common
import Command import Command
import qualified AnnexQueue import qualified Annex.Queue
import Content import Annex.Content
command :: [Command] command :: [Command]
command = [repoCommand "fix" paramPaths seek command = [repoCommand "fix" paramPaths seek
@ -39,5 +39,5 @@ perform file link = do
cleanup :: FilePath -> CommandCleanup cleanup :: FilePath -> CommandCleanup
cleanup file = do cleanup file = do
AnnexQueue.add "add" [Param "--"] [file] Annex.Queue.add "add" [Param "--"] [file]
return True return True

View file

@ -7,10 +7,10 @@
module Command.FromKey where module Command.FromKey where
import AnnexCommon import Annex.Common
import Command import Command
import qualified AnnexQueue import qualified Annex.Queue
import Content import Annex.Content
import Types.Key import Types.Key
command :: [Command] command :: [Command]
@ -39,5 +39,5 @@ perform file = do
cleanup :: FilePath -> CommandCleanup cleanup :: FilePath -> CommandCleanup
cleanup file = do cleanup file = do
AnnexQueue.add "add" [Param "--"] [file] Annex.Queue.add "add" [Param "--"] [file]
return True return True

View file

@ -7,13 +7,13 @@
module Command.Fsck where module Command.Fsck where
import AnnexCommon import Annex.Common
import Command import Command
import qualified Remote import qualified Remote
import qualified Types.Backend import qualified Types.Backend
import qualified Types.Key import qualified Types.Key
import UUID import UUID
import Content import Annex.Content
import LocationLog import LocationLog
import Trust import Trust
import Utility.DataUnits import Utility.DataUnits

View file

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

View file

@ -7,9 +7,9 @@
module Command.InAnnex where module Command.InAnnex where
import AnnexCommon import Annex.Common
import Command import Command
import Content import Annex.Content
command :: [Command] command :: [Command]
command = [repoCommand "inannex" (paramRepeating paramKey) seek command = [repoCommand "inannex" (paramRepeating paramKey) seek

View file

@ -7,7 +7,7 @@
module Command.Init where module Command.Init where
import AnnexCommon import Annex.Common
import Command import Command
import UUID import UUID
import Init import Init

View file

@ -9,7 +9,7 @@ module Command.InitRemote where
import qualified Data.Map as M import qualified Data.Map as M
import AnnexCommon import Annex.Common
import Command import Command
import qualified Remote import qualified Remote
import qualified RemoteLog import qualified RemoteLog

View file

@ -7,9 +7,9 @@
module Command.Lock where module Command.Lock where
import AnnexCommon import Annex.Common
import Command import Command
import qualified AnnexQueue import qualified Annex.Queue
import Backend import Backend
command :: [Command] command :: [Command]
@ -30,5 +30,5 @@ perform file = do
-- Checkout from HEAD to get rid of any changes that might be -- Checkout from HEAD to get rid of any changes that might be
-- staged in the index, and get back to the previous symlink to -- staged in the index, and get back to the previous symlink to
-- the content. -- the content.
AnnexQueue.add "checkout" [Param "HEAD", Param "--"] [file] Annex.Queue.add "checkout" [Param "HEAD", Param "--"] [file]
next $ return True -- no cleanup needed next $ return True -- no cleanup needed

View file

@ -10,7 +10,7 @@ module Command.Map where
import Control.Exception.Extensible import Control.Exception.Extensible
import qualified Data.Map as M import qualified Data.Map as M
import AnnexCommon import Annex.Common
import Command import Command
import qualified Git import qualified Git
import UUID import UUID

View file

@ -7,9 +7,9 @@
module Command.Merge where module Command.Merge where
import AnnexCommon import Annex.Common
import Command import Command
import qualified Branch import qualified Annex.Branch
command :: [Command] command :: [Command]
command = [repoCommand "merge" paramNothing seek command = [repoCommand "merge" paramNothing seek
@ -25,5 +25,5 @@ start = do
perform :: CommandPerform perform :: CommandPerform
perform = do perform = do
Branch.update Annex.Branch.update
next $ return True next $ return True

View file

@ -7,11 +7,11 @@
module Command.Migrate where module Command.Migrate where
import AnnexCommon import Annex.Common
import Command import Command
import qualified Backend import qualified Backend
import qualified Types.Key import qualified Types.Key
import Content import Annex.Content
import qualified Command.Add import qualified Command.Add
import Backend import Backend

View file

@ -7,12 +7,12 @@
module Command.Move where module Command.Move where
import AnnexCommon import Annex.Common
import Command import Command
import qualified Command.Drop import qualified Command.Drop
import qualified Annex import qualified Annex
import LocationLog import LocationLog
import Content import Annex.Content
import qualified Remote import qualified Remote
import UUID import UUID

View file

@ -7,10 +7,10 @@
module Command.RecvKey where module Command.RecvKey where
import AnnexCommon import Annex.Common
import Command import Command
import CmdLine import CmdLine
import Content import Annex.Content
import Utility.RsyncFile import Utility.RsyncFile
command :: [Command] command :: [Command]

View file

@ -7,7 +7,7 @@
module Command.Semitrust where module Command.Semitrust where
import AnnexCommon import Annex.Common
import Command import Command
import qualified Remote import qualified Remote
import UUID import UUID

View file

@ -7,9 +7,9 @@
module Command.SendKey where module Command.SendKey where
import AnnexCommon import Annex.Common
import Command import Command
import Content import Annex.Content
import Utility.RsyncFile import Utility.RsyncFile
command :: [Command] command :: [Command]

View file

@ -7,10 +7,10 @@
module Command.SetKey where module Command.SetKey where
import AnnexCommon import Annex.Common
import Command import Command
import LocationLog import LocationLog
import Content import Annex.Content
command :: [Command] command :: [Command]
command = [repoCommand "setkey" paramPath seek command = [repoCommand "setkey" paramPath seek

View file

@ -12,7 +12,7 @@ import qualified Data.Map as M
import qualified Data.Set as S import qualified Data.Set as S
import Data.Set (Set) import Data.Set (Set)
import AnnexCommon import Annex.Common
import qualified Types.Backend as B import qualified Types.Backend as B
import qualified Types.Remote as R import qualified Types.Remote as R
import qualified Remote import qualified Remote
@ -20,7 +20,7 @@ import qualified Command.Unused
import qualified Git import qualified Git
import Command import Command
import Utility.DataUnits import Utility.DataUnits
import Content import Annex.Content
import Types.Key import Types.Key
import Backend import Backend
import UUID import UUID

View file

@ -7,7 +7,7 @@
module Command.Trust where module Command.Trust where
import AnnexCommon import Annex.Common
import Command import Command
import qualified Remote import qualified Remote
import Trust import Trust

View file

@ -7,14 +7,14 @@
module Command.Unannex where module Command.Unannex where
import AnnexCommon import Annex.Common
import Command import Command
import qualified Command.Drop import qualified Command.Drop
import qualified Annex import qualified Annex
import qualified AnnexQueue import qualified Annex.Queue
import Utility.FileMode import Utility.FileMode
import LocationLog import LocationLog
import Content import Annex.Content
import qualified Git import qualified Git
import qualified Git.LsFiles as LsFiles import qualified Git.LsFiles as LsFiles
@ -71,6 +71,6 @@ cleanup file key = do
-- Commit staged changes at end to avoid confusing the -- Commit staged changes at end to avoid confusing the
-- pre-commit hook if this file is later added back to -- pre-commit hook if this file is later added back to
-- git as a normal, non-annexed file. -- git as a normal, non-annexed file.
AnnexQueue.add "commit" [Param "-m", Param "content removed from git annex"] [] Annex.Queue.add "commit" [Param "-m", Param "content removed from git annex"] []
return True return True

View file

@ -7,14 +7,14 @@
module Command.Uninit where module Command.Uninit where
import AnnexCommon import Annex.Common
import Command import Command
import qualified Git import qualified Git
import qualified Annex import qualified Annex
import qualified Command.Unannex import qualified Command.Unannex
import Init import Init
import qualified Branch import qualified Annex.Branch
import Content import Annex.Content
command :: [Command] command :: [Command]
command = [repoCommand "uninit" paramPaths seek command = [repoCommand "uninit" paramPaths seek
@ -46,5 +46,5 @@ cleanup = do
-- avoid normal shutdown -- avoid normal shutdown
saveState saveState
liftIO $ do liftIO $ do
Git.run g "branch" [Param "-D", Param Branch.name] Git.run g "branch" [Param "-D", Param Annex.Branch.name]
exitSuccess exitSuccess

View file

@ -7,9 +7,9 @@
module Command.Unlock where module Command.Unlock where
import AnnexCommon import Annex.Common
import Command import Command
import Content import Annex.Content
import Utility.CopyFile import Utility.CopyFile
import Utility.FileMode import Utility.FileMode

View file

@ -7,7 +7,7 @@
module Command.Untrust where module Command.Untrust where
import AnnexCommon import Annex.Common
import Command import Command
import qualified Remote import qualified Remote
import UUID import UUID

View file

@ -12,9 +12,9 @@ module Command.Unused where
import qualified Data.Set as S import qualified Data.Set as S
import qualified Data.ByteString.Lazy.Char8 as L import qualified Data.ByteString.Lazy.Char8 as L
import AnnexCommon import Annex.Common
import Command import Command
import Content import Annex.Content
import Utility.FileMode import Utility.FileMode
import LocationLog import LocationLog
import qualified Annex import qualified Annex
@ -23,8 +23,8 @@ import qualified Git.LsFiles as LsFiles
import qualified Git.LsTree as LsTree import qualified Git.LsTree as LsTree
import qualified Backend import qualified Backend
import qualified Remote import qualified Remote
import qualified Branch import qualified Annex.Branch
import CatFile import Annex.CatFile
command :: [Command] command :: [Command]
command = [repoCommand "unused" paramNothing seek command = [repoCommand "unused" paramNothing seek
@ -165,7 +165,7 @@ excludeReferenced l = do
filter ourbranches . filter ourbranches .
map words . lines . L.unpack map words . lines . L.unpack
cmpheads a b = head a == head b cmpheads a b = head a == head b
ourbranchend = '/' : Branch.name ourbranchend = '/' : Annex.Branch.name
ourbranches ws = not $ ourbranchend `isSuffixOf` last ws ourbranches ws = not $ ourbranchend `isSuffixOf` last ws
removewith [] s = return $ S.toList s removewith [] s = return $ S.toList s
removewith (a:as) s removewith (a:as) s

View file

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

View file

@ -7,10 +7,10 @@
module Command.Version where module Command.Version where
import AnnexCommon import Annex.Common
import Command import Command
import qualified Build.SysConfig as SysConfig import qualified Build.SysConfig as SysConfig
import Version import Annex.Version
command :: [Command] command :: [Command]
command = [standaloneCommand "version" paramNothing seek "show version info"] command = [standaloneCommand "version" paramNothing seek "show version info"]

View file

@ -7,7 +7,7 @@
module Command.Whereis where module Command.Whereis where
import AnnexCommon import Annex.Common
import LocationLog import LocationLog
import Command import Command
import Remote import Remote

View file

@ -7,7 +7,7 @@
module Config where module Config where
import AnnexCommon import Annex.Common
import qualified Git import qualified Git
import qualified Annex import qualified Annex

View file

@ -37,7 +37,7 @@ import Control.Exception (finally)
import System.Exit import System.Exit
import System.Environment import System.Environment
import AnnexCommon import Annex.Common
import Types.Key import Types.Key
import Types.Remote import Types.Remote
import Utility.Base64 import Utility.Base64

View file

@ -9,7 +9,7 @@ module GitAnnex where
import System.Console.GetOpt import System.Console.GetOpt
import AnnexCommon import Annex.Common
import qualified Git import qualified Git
import CmdLine import CmdLine
import Command import Command

10
Init.hs
View file

@ -11,16 +11,16 @@ module Init (
uninitialize uninitialize
) where ) where
import AnnexCommon import Annex.Common
import qualified Git import qualified Git
import qualified Branch import qualified Annex.Branch
import Version import Annex.Version
import UUID import UUID
initialize :: Annex () initialize :: Annex ()
initialize = do initialize = do
prepUUID prepUUID
Branch.create Annex.Branch.create
setVersion setVersion
gitPreCommitHookWrite gitPreCommitHookWrite
@ -35,7 +35,7 @@ ensureInitialized :: Annex ()
ensureInitialized = getVersion >>= maybe needsinit checkVersion ensureInitialized = getVersion >>= maybe needsinit checkVersion
where where
needsinit = do needsinit = do
annexed <- Branch.hasSomeBranch annexed <- Annex.Branch.hasSomeBranch
if annexed if annexed
then initialize then initialize
else error "First run: git-annex init" else error "First run: git-annex init"

View file

@ -10,13 +10,13 @@ module Limit where
import Text.Regex.PCRE.Light.Char8 import Text.Regex.PCRE.Light.Char8
import System.Path.WildMatch import System.Path.WildMatch
import AnnexCommon import Annex.Common
import qualified Annex import qualified Annex
import qualified Utility.Matcher import qualified Utility.Matcher
import qualified Remote import qualified Remote
import qualified Backend import qualified Backend
import LocationLog import LocationLog
import Content import Annex.Content
type Limit = Utility.Matcher.Token (FilePath -> Annex Bool) type Limit = Utility.Matcher.Token (FilePath -> Annex Bool)

View file

@ -21,9 +21,9 @@ module LocationLog (
logFileKey logFileKey
) where ) where
import AnnexCommon import Annex.Common
import qualified Git import qualified Git
import qualified Branch import qualified Annex.Branch
import UUID import UUID
import PresenceLog import PresenceLog
@ -43,7 +43,7 @@ keyLocations = currentLog . logFile
{- Finds all keys that have location log information. {- Finds all keys that have location log information.
- (There may be duplicate keys in the list.) -} - (There may be duplicate keys in the list.) -}
loggedKeys :: Annex [Key] loggedKeys :: Annex [Key]
loggedKeys = mapMaybe (logFileKey . takeFileName) <$> Branch.files loggedKeys = mapMaybe (logFileKey . takeFileName) <$> Annex.Branch.files
{- The filename of the log file for a given key. -} {- The filename of the log file for a given key. -}
logFile :: Key -> String logFile :: Key -> String

View file

@ -10,7 +10,7 @@ module Options where
import System.Console.GetOpt import System.Console.GetOpt
import System.Log.Logger import System.Log.Logger
import AnnexCommon import Annex.Common
import qualified Annex import qualified Annex
import Command import Command
import Limit import Limit

View file

@ -27,8 +27,8 @@ import Data.Time
import System.Locale import System.Locale
import qualified Data.Map as M import qualified Data.Map as M
import AnnexCommon import Annex.Common
import qualified Branch import qualified Annex.Branch
data LogLine = LogLine { data LogLine = LogLine {
date :: POSIXTime, date :: POSIXTime,
@ -72,13 +72,13 @@ instance Read LogLine where
ret v = [(v, "")] ret v = [(v, "")]
addLog :: FilePath -> LogLine -> Annex () addLog :: FilePath -> LogLine -> Annex ()
addLog file line = Branch.change file $ \s -> addLog file line = Annex.Branch.change file $ \s ->
showLog $ compactLog (line : parseLog s) showLog $ compactLog (line : parseLog s)
{- Reads a log file. {- Reads a log file.
- Note that the LogLines returned may be in any order. -} - Note that the LogLines returned may be in any order. -}
readLog :: FilePath -> Annex [LogLine] readLog :: FilePath -> Annex [LogLine]
readLog file = parseLog <$> Branch.get file readLog file = parseLog <$> Annex.Branch.get file
parseLog :: String -> [LogLine] parseLog :: String -> [LogLine]
parseLog = filter parsable . map read . lines parseLog = filter parsable . map read . lines

View file

@ -32,7 +32,7 @@ import qualified Data.Map as M
import Text.JSON import Text.JSON
import Text.JSON.Generic import Text.JSON.Generic
import AnnexCommon import Annex.Common
import Types.Remote import Types.Remote
import UUID import UUID
import qualified Annex import qualified Annex

View file

@ -12,7 +12,7 @@ import System.IO.Error
import qualified Data.Map as M import qualified Data.Map as M
import System.Process import System.Process
import AnnexCommon import Annex.Common
import Types.Remote import Types.Remote
import qualified Git import qualified Git
import UUID import UUID

View file

@ -11,7 +11,7 @@ import qualified Data.ByteString.Lazy.Char8 as L
import System.IO.Error import System.IO.Error
import qualified Data.Map as M import qualified Data.Map as M
import AnnexCommon import Annex.Common
import Utility.CopyFile import Utility.CopyFile
import Types.Remote import Types.Remote
import qualified Git import qualified Git

View file

@ -10,7 +10,7 @@ module Remote.Git (remote) where
import Control.Exception.Extensible import Control.Exception.Extensible
import qualified Data.Map as M import qualified Data.Map as M
import AnnexCommon import Annex.Common
import Utility.CopyFile import Utility.CopyFile
import Utility.RsyncFile import Utility.RsyncFile
import Utility.Ssh import Utility.Ssh
@ -18,7 +18,7 @@ import Types.Remote
import qualified Git import qualified Git
import qualified Annex import qualified Annex
import UUID import UUID
import qualified Content import qualified Annex.Content
import qualified Utility.Url as Url import qualified Utility.Url as Url
import Config import Config
import Init import Init
@ -121,7 +121,7 @@ inAnnex r key
| Git.repoIsUrl r = checkremote | Git.repoIsUrl r = checkremote
| otherwise = safely checklocal | otherwise = safely checklocal
where where
checklocal = onLocal r (Content.inAnnex key) checklocal = onLocal r (Annex.Content.inAnnex key)
checkremote = do checkremote = do
showAction $ "checking " ++ Git.repoDescribe r showAction $ "checking " ++ Git.repoDescribe r
inannex <- onRemote r (boolSystem, False) "inannex" inannex <- onRemote r (boolSystem, False) "inannex"
@ -164,9 +164,9 @@ copyToRemote r key
let keysrc = gitAnnexLocation g key let keysrc = gitAnnexLocation g key
-- run copy from perspective of remote -- run copy from perspective of remote
liftIO $ onLocal r $ do liftIO $ onLocal r $ do
ok <- Content.getViaTmp key $ ok <- Annex.Content.getViaTmp key $
rsyncOrCopyFile r keysrc rsyncOrCopyFile r keysrc
Content.saveState Annex.Content.saveState
return ok return ok
| Git.repoIsSsh r = do | Git.repoIsSsh r = do
g <- gitRepo g <- gitRepo

View file

@ -9,7 +9,7 @@ module Remote.Helper.Encryptable where
import qualified Data.Map as M import qualified Data.Map as M
import AnnexCommon import Annex.Common
import Types.Remote import Types.Remote
import Crypto import Crypto
import qualified Annex import qualified Annex

View file

@ -9,7 +9,7 @@ module Remote.Helper.Special where
import qualified Data.Map as M import qualified Data.Map as M
import AnnexCommon import Annex.Common
import Types.Remote import Types.Remote
import qualified Git import qualified Git
import UUID import UUID

View file

@ -12,12 +12,12 @@ import qualified Data.Map as M
import System.IO.Error (try) import System.IO.Error (try)
import System.Exit import System.Exit
import AnnexCommon import Annex.Common
import Types.Remote import Types.Remote
import qualified Git import qualified Git
import UUID import UUID
import Config import Config
import Content import Annex.Content
import Remote.Helper.Special import Remote.Helper.Special
import Remote.Helper.Encryptable import Remote.Helper.Encryptable
import Crypto import Crypto

View file

@ -10,12 +10,12 @@ module Remote.Rsync (remote) where
import qualified Data.ByteString.Lazy.Char8 as L import qualified Data.ByteString.Lazy.Char8 as L
import qualified Data.Map as M import qualified Data.Map as M
import AnnexCommon import Annex.Common
import Types.Remote import Types.Remote
import qualified Git import qualified Git
import UUID import UUID
import Config import Config
import Content import Annex.Content
import Remote.Helper.Special import Remote.Helper.Special
import Remote.Helper.Encryptable import Remote.Helper.Encryptable
import Crypto import Crypto

View file

@ -17,7 +17,7 @@ import Data.Char
import System.Environment import System.Environment
import System.Posix.Env (setEnv) import System.Posix.Env (setEnv)
import AnnexCommon import Annex.Common
import Types.Remote import Types.Remote
import Types.Key import Types.Key
import qualified Git import qualified Git
@ -26,7 +26,7 @@ import Config
import Remote.Helper.Special import Remote.Helper.Special
import Remote.Helper.Encryptable import Remote.Helper.Encryptable
import Crypto import Crypto
import Content import Annex.Content
import Utility.Base64 import Utility.Base64
remote :: RemoteType Annex remote :: RemoteType Annex

View file

@ -10,7 +10,7 @@ module Remote.Web (
setUrl setUrl
) where ) where
import AnnexCommon import Annex.Common
import Types.Remote import Types.Remote
import qualified Git import qualified Git
import UUID import UUID

View file

@ -18,8 +18,8 @@ module RemoteLog (
import qualified Data.Map as M import qualified Data.Map as M
import Data.Char import Data.Char
import AnnexCommon import Annex.Common
import qualified Branch import qualified Annex.Branch
import Types.Remote import Types.Remote
import UUID import UUID
@ -29,7 +29,7 @@ remoteLog = "remote.log"
{- Adds or updates a remote's config in the log. -} {- Adds or updates a remote's config in the log. -}
configSet :: UUID -> RemoteConfig -> Annex () configSet :: UUID -> RemoteConfig -> Annex ()
configSet u c = Branch.change remoteLog $ configSet u c = Annex.Branch.change remoteLog $
serialize . M.insert u c . remoteLogParse serialize . M.insert u c . remoteLogParse
where where
serialize = unlines . sort . map toline . M.toList serialize = unlines . sort . map toline . M.toList
@ -37,7 +37,7 @@ configSet u c = Branch.change remoteLog $
{- Map of remotes by uuid containing key/value config maps. -} {- Map of remotes by uuid containing key/value config maps. -}
readRemoteLog :: Annex (M.Map UUID RemoteConfig) readRemoteLog :: Annex (M.Map UUID RemoteConfig)
readRemoteLog = remoteLogParse <$> Branch.get remoteLog readRemoteLog = remoteLogParse <$> Annex.Branch.get remoteLog
remoteLogParse :: String -> M.Map UUID RemoteConfig remoteLogParse :: String -> M.Map UUID RemoteConfig
remoteLogParse s = remoteLogParse s =

View file

@ -15,9 +15,9 @@ module Trust (
import qualified Data.Map as M import qualified Data.Map as M
import AnnexCommon import Annex.Common
import Types.TrustLevel import Types.TrustLevel
import qualified Branch import qualified Annex.Branch
import UUID import UUID
import qualified Annex import qualified Annex
@ -40,7 +40,7 @@ trustMap = do
Just m -> return m Just m -> return m
Nothing -> do Nothing -> do
overrides <- Annex.getState Annex.forcetrust overrides <- Annex.getState Annex.forcetrust
l <- Branch.get trustLog l <- Annex.Branch.get trustLog
let m = M.fromList $ trustMapParse l ++ overrides let m = M.fromList $ trustMapParse l ++ overrides
Annex.changeState $ \s -> s { Annex.trustmap = Just m } Annex.changeState $ \s -> s { Annex.trustmap = Just m }
return m return m
@ -62,7 +62,7 @@ trustSet :: UUID -> TrustLevel -> Annex ()
trustSet uuid level = do trustSet uuid level = do
when (null uuid) $ when (null uuid) $
error "unknown UUID; cannot modify trust level" error "unknown UUID; cannot modify trust level"
Branch.change trustLog $ Annex.Branch.change trustLog $
serialize . M.insert uuid level . M.fromList . trustMapParse serialize . M.insert uuid level . M.fromList . trustMapParse
Annex.changeState $ \s -> s { Annex.trustmap = Nothing } Annex.changeState $ \s -> s { Annex.trustmap = Nothing }
where where

View file

@ -24,9 +24,9 @@ module UUID (
import qualified Data.Map as M import qualified Data.Map as M
import AnnexCommon import Annex.Common
import qualified Git import qualified Git
import qualified Branch import qualified Annex.Branch
import Types.UUID import Types.UUID
import qualified Build.SysConfig as SysConfig import qualified Build.SysConfig as SysConfig
import Config import Config
@ -82,14 +82,14 @@ prepUUID = do
{- Records a description for a uuid in the uuidLog. -} {- Records a description for a uuid in the uuidLog. -}
describeUUID :: UUID -> String -> Annex () describeUUID :: UUID -> String -> Annex ()
describeUUID uuid desc = Branch.change uuidLog $ describeUUID uuid desc = Annex.Branch.change uuidLog $
serialize . M.insert uuid desc . parse serialize . M.insert uuid desc . parse
where where
serialize m = unlines $ map (\(u, d) -> u++" "++d) $ M.toList m serialize m = unlines $ map (\(u, d) -> u++" "++d) $ M.toList m
{- Read the uuidLog into a Map -} {- Read the uuidLog into a Map -}
uuidMap :: Annex (M.Map UUID String) uuidMap :: Annex (M.Map UUID String)
uuidMap = parse <$> Branch.get uuidLog uuidMap = parse <$> Annex.Branch.get uuidLog
parse :: String -> M.Map UUID String parse :: String -> M.Map UUID String
parse = M.fromList . map pair . lines parse = M.fromList . map pair . lines

View file

@ -7,8 +7,8 @@
module Upgrade where module Upgrade where
import AnnexCommon import Annex.Common
import Version import Annex.Version
import qualified Upgrade.V0 import qualified Upgrade.V0
import qualified Upgrade.V1 import qualified Upgrade.V1
import qualified Upgrade.V2 import qualified Upgrade.V2

View file

@ -9,8 +9,8 @@ module Upgrade.V0 where
import System.IO.Error (try) import System.IO.Error (try)
import AnnexCommon import Annex.Common
import Content import Annex.Content
import qualified Upgrade.V1 import qualified Upgrade.V1
upgrade :: Annex Bool upgrade :: Annex Bool

View file

@ -11,15 +11,15 @@ import System.IO.Error (try)
import System.Posix.Types import System.Posix.Types
import Data.Char import Data.Char
import AnnexCommon import Annex.Common
import Types.Key import Types.Key
import Content import Annex.Content
import PresenceLog import PresenceLog
import qualified AnnexQueue import qualified Annex.Queue
import qualified Git import qualified Git
import qualified Git.LsFiles as LsFiles import qualified Git.LsFiles as LsFiles
import Backend import Backend
import Version import Annex.Version
import Utility.FileMode import Utility.FileMode
import qualified Upgrade.V2 import qualified Upgrade.V2
@ -60,7 +60,7 @@ upgrade = do
updateSymlinks updateSymlinks
moveLocationLogs moveLocationLogs
AnnexQueue.flush True Annex.Queue.flush True
setVersion setVersion
Upgrade.V2.upgrade Upgrade.V2.upgrade
@ -94,7 +94,7 @@ updateSymlinks = do
link <- calcGitLink f k link <- calcGitLink f k
liftIO $ removeFile f liftIO $ removeFile f
liftIO $ createSymbolicLink link f liftIO $ createSymbolicLink link f
AnnexQueue.add "add" [Param "--"] [f] Annex.Queue.add "add" [Param "--"] [f]
moveLocationLogs :: Annex () moveLocationLogs :: Annex ()
moveLocationLogs = do moveLocationLogs = do
@ -124,9 +124,9 @@ moveLocationLogs = do
old <- liftIO $ readLog1 f old <- liftIO $ readLog1 f
new <- liftIO $ readLog1 dest new <- liftIO $ readLog1 dest
liftIO $ writeLog1 dest (old++new) liftIO $ writeLog1 dest (old++new)
AnnexQueue.add "add" [Param "--"] [dest] Annex.Queue.add "add" [Param "--"] [dest]
AnnexQueue.add "add" [Param "--"] [f] Annex.Queue.add "add" [Param "--"] [f]
AnnexQueue.add "rm" [Param "--quiet", Param "-f", Param "--"] [f] Annex.Queue.add "rm" [Param "--quiet", Param "-f", Param "--"] [f]
oldlog2key :: FilePath -> Maybe (FilePath, Key) oldlog2key :: FilePath -> Maybe (FilePath, Key)
oldlog2key l = oldlog2key l =

View file

@ -7,11 +7,11 @@
module Upgrade.V2 where module Upgrade.V2 where
import AnnexCommon import Annex.Common
import qualified Git import qualified Git
import qualified Branch import qualified Annex.Branch
import LocationLog import LocationLog
import Content import Annex.Content
olddir :: Git.Repo -> FilePath olddir :: Git.Repo -> FilePath
olddir g olddir g
@ -39,7 +39,7 @@ upgrade = do
g <- gitRepo g <- gitRepo
let bare = Git.repoIsLocalBare g let bare = Git.repoIsLocalBare g
Branch.create Annex.Branch.create
showProgress showProgress
e <- liftIO $ doesDirectoryExist (olddir g) e <- liftIO $ doesDirectoryExist (olddir g)
@ -75,7 +75,7 @@ inject :: FilePath -> FilePath -> Annex ()
inject source dest = do inject source dest = do
g <- gitRepo g <- gitRepo
new <- liftIO (readFile $ olddir g </> source) new <- liftIO (readFile $ olddir g </> source)
Branch.change dest $ \prev -> Annex.Branch.change dest $ \prev ->
unlines $ nub $ lines prev ++ lines new unlines $ nub $ lines prev ++ lines new
showProgress showProgress
@ -85,8 +85,8 @@ logFiles dir = return . filter (".log" `isSuffixOf`)
push :: Annex () push :: Annex ()
push = do push = do
origin_master <- Branch.refExists "origin/master" origin_master <- Annex.Branch.refExists "origin/master"
origin_gitannex <- Branch.hasOrigin origin_gitannex <- Annex.Branch.hasOrigin
case (origin_master, origin_gitannex) of case (origin_master, origin_gitannex) of
(_, True) -> do (_, True) -> do
-- Merge in the origin's git-annex branch, -- Merge in the origin's git-annex branch,
@ -94,20 +94,20 @@ push = do
-- will immediately work. Not pushed here, -- will immediately work. Not pushed here,
-- because it's less obnoxious to let the user -- because it's less obnoxious to let the user
-- push. -- push.
Branch.update Annex.Branch.update
(True, False) -> do (True, False) -> do
-- push git-annex to origin, so that -- push git-annex to origin, so that
-- "git push" will from then on -- "git push" will from then on
-- automatically push it -- automatically push it
Branch.update -- just in case Annex.Branch.update -- just in case
showAction "pushing new git-annex branch to origin" showAction "pushing new git-annex branch to origin"
showOutput showOutput
g <- gitRepo g <- gitRepo
liftIO $ Git.run g "push" [Param "origin", Param Branch.name] liftIO $ Git.run g "push" [Param "origin", Param Annex.Branch.name]
_ -> do _ -> do
-- no origin exists, so just let the user -- no origin exists, so just let the user
-- know about the new branch -- know about the new branch
Branch.update Annex.Branch.update
showLongNote $ showLongNote $
"git-annex branch created\n" ++ "git-annex branch created\n" ++
"Be sure to push this branch when pushing to remotes.\n" "Be sure to push this branch when pushing to remotes.\n"

View file

@ -7,7 +7,7 @@
import System.Environment import System.Environment
import AnnexCommon import Annex.Common
import qualified Git import qualified Git
import CmdLine import CmdLine
import Command import Command