summaryrefslogtreecommitdiff
path: root/Upgrade
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2011-10-04 00:40:47 -0400
committerGravatar Joey Hess <joey@kitenet.net>2011-10-04 00:59:08 -0400
commitcfe21e85e7fba61ac588e210f2a9b75f8d081f42 (patch)
tree3237aa5460cb38254a44a6462c83db3c2276c229 /Upgrade
parentff21fd4a652cc6516d0e06ab885adf1c93eddced (diff)
rename
Diffstat (limited to 'Upgrade')
-rw-r--r--Upgrade/V0.hs4
-rw-r--r--Upgrade/V1.hs18
-rw-r--r--Upgrade/V2.hs22
3 files changed, 22 insertions, 22 deletions
diff --git a/Upgrade/V0.hs b/Upgrade/V0.hs
index f8e6cda56..af91741a0 100644
--- a/Upgrade/V0.hs
+++ b/Upgrade/V0.hs
@@ -9,8 +9,8 @@ module Upgrade.V0 where
import System.IO.Error (try)
-import AnnexCommon
-import Content
+import Annex.Common
+import Annex.Content
import qualified Upgrade.V1
upgrade :: Annex Bool
diff --git a/Upgrade/V1.hs b/Upgrade/V1.hs
index bc50b857c..f4e44acdc 100644
--- a/Upgrade/V1.hs
+++ b/Upgrade/V1.hs
@@ -11,15 +11,15 @@ import System.IO.Error (try)
import System.Posix.Types
import Data.Char
-import AnnexCommon
+import Annex.Common
import Types.Key
-import Content
+import Annex.Content
import PresenceLog
-import qualified AnnexQueue
+import qualified Annex.Queue
import qualified Git
import qualified Git.LsFiles as LsFiles
import Backend
-import Version
+import Annex.Version
import Utility.FileMode
import qualified Upgrade.V2
@@ -60,7 +60,7 @@ upgrade = do
updateSymlinks
moveLocationLogs
- AnnexQueue.flush True
+ Annex.Queue.flush True
setVersion
Upgrade.V2.upgrade
@@ -94,7 +94,7 @@ updateSymlinks = do
link <- calcGitLink f k
liftIO $ removeFile f
liftIO $ createSymbolicLink link f
- AnnexQueue.add "add" [Param "--"] [f]
+ Annex.Queue.add "add" [Param "--"] [f]
moveLocationLogs :: Annex ()
moveLocationLogs = do
@@ -124,9 +124,9 @@ moveLocationLogs = do
old <- liftIO $ readLog1 f
new <- liftIO $ readLog1 dest
liftIO $ writeLog1 dest (old++new)
- AnnexQueue.add "add" [Param "--"] [dest]
- AnnexQueue.add "add" [Param "--"] [f]
- AnnexQueue.add "rm" [Param "--quiet", Param "-f", Param "--"] [f]
+ Annex.Queue.add "add" [Param "--"] [dest]
+ Annex.Queue.add "add" [Param "--"] [f]
+ Annex.Queue.add "rm" [Param "--quiet", Param "-f", Param "--"] [f]
oldlog2key :: FilePath -> Maybe (FilePath, Key)
oldlog2key l =
diff --git a/Upgrade/V2.hs b/Upgrade/V2.hs
index 922dfff28..8ac26dc52 100644
--- a/Upgrade/V2.hs
+++ b/Upgrade/V2.hs
@@ -7,11 +7,11 @@
module Upgrade.V2 where
-import AnnexCommon
+import Annex.Common
import qualified Git
-import qualified Branch
+import qualified Annex.Branch
import LocationLog
-import Content
+import Annex.Content
olddir :: Git.Repo -> FilePath
olddir g
@@ -39,7 +39,7 @@ upgrade = do
g <- gitRepo
let bare = Git.repoIsLocalBare g
- Branch.create
+ Annex.Branch.create
showProgress
e <- liftIO $ doesDirectoryExist (olddir g)
@@ -75,7 +75,7 @@ inject :: FilePath -> FilePath -> Annex ()
inject source dest = do
g <- gitRepo
new <- liftIO (readFile $ olddir g </> source)
- Branch.change dest $ \prev ->
+ Annex.Branch.change dest $ \prev ->
unlines $ nub $ lines prev ++ lines new
showProgress
@@ -85,8 +85,8 @@ logFiles dir = return . filter (".log" `isSuffixOf`)
push :: Annex ()
push = do
- origin_master <- Branch.refExists "origin/master"
- origin_gitannex <- Branch.hasOrigin
+ origin_master <- Annex.Branch.refExists "origin/master"
+ origin_gitannex <- Annex.Branch.hasOrigin
case (origin_master, origin_gitannex) of
(_, True) -> do
-- Merge in the origin's git-annex branch,
@@ -94,20 +94,20 @@ push = do
-- will immediately work. Not pushed here,
-- because it's less obnoxious to let the user
-- push.
- Branch.update
+ Annex.Branch.update
(True, False) -> do
-- push git-annex to origin, so that
-- "git push" will from then on
-- automatically push it
- Branch.update -- just in case
+ Annex.Branch.update -- just in case
showAction "pushing new git-annex branch to origin"
showOutput
g <- gitRepo
- liftIO $ Git.run g "push" [Param "origin", Param Branch.name]
+ liftIO $ Git.run g "push" [Param "origin", Param Annex.Branch.name]
_ -> do
-- no origin exists, so just let the user
-- know about the new branch
- Branch.update
+ Annex.Branch.update
showLongNote $
"git-annex branch created\n" ++
"Be sure to push this branch when pushing to remotes.\n"