aboutsummaryrefslogtreecommitdiff
path: root/Upgrade/V2.hs
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2011-06-22 16:02:43 -0400
committerGravatar Joey Hess <joey@kitenet.net>2011-06-22 16:03:09 -0400
commit5c706d1ec48172f98e1826684ab380a69079b66a (patch)
tree4c73aa9383105a1d640271f5b57a771fbd1657da /Upgrade/V2.hs
parent80274f4c92397a88c62bf82459fe0c1a9bf03bf7 (diff)
stop undoing gitattributes on uninit
v2 upgrade will undo them
Diffstat (limited to 'Upgrade/V2.hs')
-rw-r--r--Upgrade/V2.hs48
1 files changed, 48 insertions, 0 deletions
diff --git a/Upgrade/V2.hs b/Upgrade/V2.hs
new file mode 100644
index 000000000..deb231d52
--- /dev/null
+++ b/Upgrade/V2.hs
@@ -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