convert to ByteString

This commit is contained in:
Joey Hess 2019-01-14 14:02:47 -04:00
parent 0acbbf208f
commit 0a8d93cb8a
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38

View file

@ -1,13 +1,17 @@
{- git-annex file locations {- git-annex file locations
- -
- Copyright 2010-2017 Joey Hess <id@joeyh.name> - Copyright 2010-2019 Joey Hess <id@joeyh.name>
- -
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
{-# LANGUAGE OverloadedStrings #-}
module Annex.Locations ( module Annex.Locations (
keyFile, keyFile,
keyFile',
fileKey, fileKey,
fileKey',
keyPaths, keyPaths,
keyPath, keyPath,
annexDir, annexDir,
@ -80,6 +84,8 @@ module Annex.Locations (
import Data.Char import Data.Char
import Data.Default import Data.Default
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString.Char8 as S8
import Common import Common
import Key import Key
@ -476,8 +482,8 @@ preSanitizeKeyName' resanitize = concatMap escape
where where
escape c escape c
| isAsciiUpper c || isAsciiLower c || isDigit c = [c] | isAsciiUpper c || isAsciiLower c || isDigit c = [c]
| c `elem` ".-_" = [c] -- common, assumed safe | c `elem` ['.', '-', '_'] = [c] -- common, assumed safe
| c `elem` "/%:" = [c] -- handled by keyFile | c `elem` ['/', '%', ':'] = [c] -- handled by keyFile
-- , is safe and uncommon, so will be used to escape -- , is safe and uncommon, so will be used to escape
-- other characters. By itself, it is escaped to -- other characters. By itself, it is escaped to
-- doubled form. -- doubled form.
@ -506,25 +512,33 @@ reSanitizeKeyName = preSanitizeKeyName' True
- can cause existing objects to get lost. - can cause existing objects to get lost.
-} -}
keyFile :: Key -> FilePath keyFile :: Key -> FilePath
keyFile = concatMap esc . serializeKey keyFile = fromRawFilePath . keyFile'
keyFile' :: Key -> RawFilePath
keyFile' = S8.concatMap esc . L.toStrict . serializeKey'
where where
esc '&' = "&a" esc '&' = "&a"
esc '%' = "&s" esc '%' = "&s"
esc ':' = "&c" esc ':' = "&c"
esc '/' = "%" esc '/' = "%"
esc c = [c] esc c = S8.singleton c
{- Reverses keyFile, converting a filename fragment (ie, the basename of {- Reverses keyFile, converting a filename fragment (ie, the basename of
- the symlink target) into a key. -} - the symlink target) into a key. -}
fileKey :: FilePath -> Maybe Key fileKey :: FilePath -> Maybe Key
fileKey = deserializeKey . unesc [] fileKey = fileKey' . toRawFilePath
fileKey' :: RawFilePath -> Maybe Key
fileKey' = deserializeKey' . S8.intercalate "/" . map go . S8.split '%'
where where
unesc r [] = reverse r go :: S8.ByteString -> S8.ByteString
unesc r ('%':cs) = unesc ('/':r) cs go = S8.concat . map (unesc . S8.uncons) . S8.split '&'
unesc r ('&':'c':cs) = unesc (':':r) cs unesc :: Maybe (Char, S8.ByteString) -> S8.ByteString
unesc r ('&':'s':cs) = unesc ('%':r) cs unesc Nothing = mempty
unesc r ('&':'a':cs) = unesc ('&':r) cs unesc (Just ('c', b)) = S8.cons ':' b
unesc r (c:cs) = unesc (c:r) cs unesc (Just ('s', b)) = S8.cons '%' b
unesc (Just ('a', b)) = S8.cons '&' b
unesc (Just (c, b)) = S8.cons c b
{- A location to store a key on a special remote that uses a filesystem. {- A location to store a key on a special remote that uses a filesystem.
- A directory hash is used, to protect against filesystems that dislike - A directory hash is used, to protect against filesystems that dislike