stop undoing gitattributes on uninit
v2 upgrade will undo them
This commit is contained in:
parent
80274f4c92
commit
5c706d1ec4
2 changed files with 48 additions and 11 deletions
|
@ -34,10 +34,7 @@ start = do
|
||||||
perform :: CommandPerform
|
perform :: CommandPerform
|
||||||
perform = do
|
perform = do
|
||||||
g <- Annex.gitRepo
|
g <- Annex.gitRepo
|
||||||
|
|
||||||
gitPreCommitHookUnWrite g
|
gitPreCommitHookUnWrite g
|
||||||
liftIO $ gitAttributesUnWrite g
|
|
||||||
|
|
||||||
next $ return True
|
next $ return True
|
||||||
|
|
||||||
gitPreCommitHookUnWrite :: Git.Repo -> Annex ()
|
gitPreCommitHookUnWrite :: Git.Repo -> Annex ()
|
||||||
|
@ -50,11 +47,3 @@ gitPreCommitHookUnWrite repo = do
|
||||||
else warning $ "pre-commit hook (" ++ hook ++
|
else warning $ "pre-commit hook (" ++ hook ++
|
||||||
") contents modified; not deleting." ++
|
") contents modified; not deleting." ++
|
||||||
" Edit it to remove call to git annex."
|
" Edit it to remove call to git annex."
|
||||||
|
|
||||||
gitAttributesUnWrite :: Git.Repo -> IO ()
|
|
||||||
gitAttributesUnWrite repo = do
|
|
||||||
let attributes = Git.attributes repo
|
|
||||||
whenM (doesFileExist attributes) $ do
|
|
||||||
c <- readFileStrict attributes
|
|
||||||
safeWriteFile attributes $ unlines $
|
|
||||||
filter (\l -> not $ l `elem` Command.Init.attrLines) $ lines c
|
|
||||||
|
|
48
Upgrade/V2.hs
Normal file
48
Upgrade/V2.hs
Normal file
|
@ -0,0 +1,48 @@
|
||||||
|
{- git-annex v2 -> v2 upgrade support
|
||||||
|
-
|
||||||
|
- Copyright 2011 Joey Hess <joey@kitenet.net>
|
||||||
|
-
|
||||||
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
|
-}
|
||||||
|
|
||||||
|
module Upgrade.V1 where
|
||||||
|
|
||||||
|
import System.IO.Error (try)
|
||||||
|
import System.Directory
|
||||||
|
import Control.Monad.State (liftIO)
|
||||||
|
import Control.Monad (filterM, forM_, unless)
|
||||||
|
import System.Posix.Files
|
||||||
|
import System.FilePath
|
||||||
|
import Data.String.Utils
|
||||||
|
import System.Posix.Types
|
||||||
|
import Data.Maybe
|
||||||
|
import Data.Char
|
||||||
|
|
||||||
|
import Types.Key
|
||||||
|
import Content
|
||||||
|
import Types
|
||||||
|
import Locations
|
||||||
|
import LocationLog
|
||||||
|
import qualified Annex
|
||||||
|
import qualified AnnexQueue
|
||||||
|
import qualified GitRepo as Git
|
||||||
|
import Backend
|
||||||
|
import Messages
|
||||||
|
import Version
|
||||||
|
import Utility
|
||||||
|
import qualified Command.Init
|
||||||
|
|
||||||
|
{- Old .gitattributes contents, not needed anymore. -}
|
||||||
|
attrLines :: [String]
|
||||||
|
attrLines =
|
||||||
|
[ stateDir </> "*.log merge=union"
|
||||||
|
, stateDir </> "*/*/*.log merge=union"
|
||||||
|
]
|
||||||
|
|
||||||
|
gitAttributesUnWrite :: Git.Repo -> IO ()
|
||||||
|
gitAttributesUnWrite repo = do
|
||||||
|
let attributes = Git.attributes repo
|
||||||
|
whenM (doesFileExist attributes) $ do
|
||||||
|
c <- readFileStrict attributes
|
||||||
|
safeWriteFile attributes $ unlines $
|
||||||
|
filter (\l -> not $ l `elem` attrLines) $ lines c
|
Loading…
Add table
Add a link
Reference in a new issue