rename
This commit is contained in:
parent
ff21fd4a65
commit
cfe21e85e7
73 changed files with 173 additions and 173 deletions
|
@ -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
|
||||
|
|
|
@ -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 =
|
||||
|
|
|
@ -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"
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue