summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Command/Unused.hs8
-rw-r--r--Utility/FileSystemEncoding.hs16
-rw-r--r--debian/changelog1
3 files changed, 20 insertions, 5 deletions
diff --git a/Command/Unused.hs b/Command/Unused.hs
index 03a709534..b115eee83 100644
--- a/Command/Unused.hs
+++ b/Command/Unused.hs
@@ -10,8 +10,7 @@
module Command.Unused where
import qualified Data.Set as S
-import qualified Data.Text.Lazy as L
-import qualified Data.Text.Lazy.Encoding as L
+import qualified Data.ByteString.Lazy as L
import Data.BloomFilter
import Data.BloomFilter.Easy
import Data.BloomFilter.Hash
@@ -265,8 +264,9 @@ withKeysReferencedInGitRef a ref = do
go [] = noop
go (l:ls)
| isSymLink (LsTree.mode l) = do
- content <- L.decodeUtf8 <$> catFile ref (LsTree.file l)
- case fileKey (takeFileName $ L.unpack content) of
+ content <- encodeW8 . L.unpack
+ <$> catFile ref (LsTree.file l)
+ case fileKey (takeFileName content) of
Nothing -> go ls
Just k -> do
a k
diff --git a/Utility/FileSystemEncoding.hs b/Utility/FileSystemEncoding.hs
index cf1a6a731..d027ede48 100644
--- a/Utility/FileSystemEncoding.hs
+++ b/Utility/FileSystemEncoding.hs
@@ -13,6 +13,8 @@ import Foreign.C
import System.IO
import System.IO.Unsafe
import qualified Data.Hash.MD5 as MD5
+import Data.Word
+import Data.Bits.Utils
{- Sets a Handle to use the filesystem encoding. This causes data
- written or read from it to be encoded/decoded the same
@@ -29,7 +31,7 @@ withFilePath :: FilePath -> (CString -> IO a) -> IO a
withFilePath fp f = Encoding.getFileSystemEncoding
>>= \enc -> GHC.withCString enc fp f
-{- Encodes a FilePath into a Str, applying the filesystem encoding.
+{- Encodes a FilePath into a Md5.Str, applying the filesystem encoding.
-
- This use of unsafePerformIO is belived to be safe; GHC's interface
- only allows doing this conversion with CStrings, and the CString buffer
@@ -41,3 +43,15 @@ encodeFilePath :: FilePath -> MD5.Str
encodeFilePath fp = MD5.Str $ unsafePerformIO $ do
enc <- Encoding.getFileSystemEncoding
GHC.withCString enc fp $ GHC.peekCString Encoding.char8
+
+{- Converts a [Word8] to a FilePath, encoding using the filesystem encoding.
+ -
+ - w82c produces a String, which may contain Chars that are invalid
+ - unicode. From there, this is really a simple matter of applying the
+ - file system encoding, only complicated by GHC's interface to doing so.
+ -}
+{-# NOINLINE encodeW8 #-}
+encodeW8 :: [Word8] -> FilePath
+encodeW8 w8 = unsafePerformIO $ do
+ enc <- Encoding.getFileSystemEncoding
+ GHC.withCString Encoding.char8 (w82s w8) $ GHC.peekCString enc
diff --git a/debian/changelog b/debian/changelog
index 9a47447ce..bc9932d52 100644
--- a/debian/changelog
+++ b/debian/changelog
@@ -4,6 +4,7 @@ git-annex (3.20120616) UNRELEASED; urgency=low
files and automatically annexes new files, etc, so you don't need
to manually run git commands when manipulating files.
* Enable diskfree on kfreebsd, using statvfs.
+ * unused: Fix crash when key names contain invalid utf8.
-- Joey Hess <joeyh@debian.org> Tue, 12 Jun 2012 11:35:59 -0400