summaryrefslogtreecommitdiff
path: root/Annex
diff options
context:
space:
mode:
Diffstat (limited to 'Annex')
-rw-r--r--Annex/Branch.hs10
-rw-r--r--Annex/Journal.hs6
2 files changed, 8 insertions, 8 deletions
diff --git a/Annex/Branch.hs b/Annex/Branch.hs
index 94c4c029c..7a75d8acf 100644
--- a/Annex/Branch.hs
+++ b/Annex/Branch.hs
@@ -25,9 +25,10 @@ module Annex.Branch (
performTransitions,
) where
-import qualified Data.ByteString.Lazy.Char8 as L
+import qualified Data.ByteString.Lazy as L
import qualified Data.Set as S
import qualified Data.Map as M
+import Data.Bits.Utils
import Common.Annex
import Annex.BranchState
@@ -199,7 +200,7 @@ getHistorical :: RefDate -> FilePath -> Annex String
getHistorical date = getRef (Git.Ref.dateRef fullname date)
getRef :: Ref -> FilePath -> Annex String
-getRef ref file = withIndex $ L.unpack <$> catFile ref file
+getRef ref file = withIndex $ decodeBS <$> catFile ref file
{- Applies a function to modifiy the content of a file.
-
@@ -259,7 +260,8 @@ commitIndex' jl branchref message parents = do
where
-- look for "parent ref" lines and return the refs
commitparents = map (Git.Ref . snd) . filter isparent .
- map (toassoc . L.unpack) . L.lines
+ map (toassoc . decodeBS) . L.split newline
+ newline = c2w8 '\n'
toassoc = separate (== ' ')
isparent (k,_) = k == "parent"
@@ -432,7 +434,7 @@ handleTransitions jl localts refs = do
return True
where
getreftransition ref = do
- ts <- parseTransitionsStrictly "remote" . L.unpack
+ ts <- parseTransitionsStrictly "remote" . decodeBS
<$> catFile ref transitionsLog
return (ref, ts)
diff --git a/Annex/Journal.hs b/Annex/Journal.hs
index 395e81d29..dcd3779de 100644
--- a/Annex/Journal.hs
+++ b/Annex/Journal.hs
@@ -13,8 +13,6 @@
module Annex.Journal where
-import System.IO.Binary
-
import Common.Annex
import Annex.Exception
import qualified Git
@@ -42,7 +40,7 @@ setJournalFile _jl file content = do
jfile <- fromRepo $ journalFile file
let tmpfile = tmp </> takeFileName jfile
liftIO $ do
- writeBinaryFile tmpfile content
+ writeFileAnyEncoding tmpfile content
moveFile tmpfile jfile
{- Gets any journalled content for a file in the branch. -}
@@ -54,7 +52,7 @@ getJournalFile _jl = getJournalFileStale
- changes. -}
getJournalFileStale :: FilePath -> Annex (Maybe String)
getJournalFileStale file = inRepo $ \g -> catchMaybeIO $
- readFileStrict $ journalFile file g
+ readFileStrictAnyEncoding $ journalFile file g
{- List of files that have updated content in the journal. -}
getJournalledFiles :: JournalLocked -> Annex [FilePath]