simplify base64 to only use ByteString
Note the use of fromString and toString from Data.ByteString.UTF8 dated back to commit9b93278e8a
. Back then it was using the dataenc package for base64, which operated on Word8 and String. But with the switch to sandi, it uses ByteString, and indeed fromB64' and toB64' were already using ByteString without that complication. So I think there is no risk of such an encoding related breakage. I also tested the case that9b93278e8a
fixed: git-annex metadata -s foo='a …' x git-annex metadata x metadata x foo=a … In Remote.Helper.Encryptable, it was avoiding using Utility.Base64 because of that UTF8 conversion. Since that's no longer done, it can just use it now.
This commit is contained in:
parent
985dd38847
commit
3742263c99
7 changed files with 27 additions and 71 deletions
|
@ -1,55 +1,25 @@
|
|||
{- Simple Base64 encoding
|
||||
-
|
||||
- Copyright 2011-2019 Joey Hess <id@joeyh.name>
|
||||
- Copyright 2011-2023 Joey Hess <id@joeyh.name>
|
||||
-
|
||||
- License: BSD-2-clause
|
||||
-}
|
||||
|
||||
{-# LANGUAGE PackageImports #-}
|
||||
|
||||
module Utility.Base64 where
|
||||
|
||||
import Utility.FileSystemEncoding
|
||||
import Utility.QuickCheck
|
||||
import Utility.Exception
|
||||
|
||||
import qualified "sandi" Codec.Binary.Base64 as B64
|
||||
import Codec.Binary.Base64 as B64
|
||||
import Data.Maybe
|
||||
import qualified Data.ByteString as B
|
||||
import Data.ByteString.UTF8 (fromString, toString)
|
||||
import Data.Char
|
||||
|
||||
-- | This uses the FileSystemEncoding, so it can be used on Strings
|
||||
-- that represent filepaths containing arbitrarily encoded characters.
|
||||
toB64 :: String -> String
|
||||
toB64 = toString . B64.encode . encodeBS
|
||||
toB64 :: B.ByteString -> B.ByteString
|
||||
toB64 = B64.encode
|
||||
|
||||
toB64' :: B.ByteString -> B.ByteString
|
||||
toB64' = B64.encode
|
||||
fromB64Maybe :: B.ByteString -> Maybe (B.ByteString)
|
||||
fromB64Maybe = either (const Nothing) Just . B64.decode
|
||||
|
||||
fromB64Maybe :: String -> Maybe String
|
||||
fromB64Maybe s = either (const Nothing) (Just . decodeBS)
|
||||
(B64.decode $ fromString s)
|
||||
|
||||
fromB64Maybe' :: B.ByteString -> Maybe (B.ByteString)
|
||||
fromB64Maybe' = either (const Nothing) Just . B64.decode
|
||||
|
||||
fromB64 :: String -> String
|
||||
fromB64 :: B.ByteString -> B.ByteString
|
||||
fromB64 = fromMaybe bad . fromB64Maybe
|
||||
where
|
||||
bad = giveup "bad base64 encoded data"
|
||||
|
||||
fromB64' :: B.ByteString -> B.ByteString
|
||||
fromB64' = fromMaybe bad . fromB64Maybe'
|
||||
where
|
||||
bad = giveup "bad base64 encoded data"
|
||||
|
||||
-- Only ascii strings are tested, because an arbitrary string may contain
|
||||
-- characters not encoded using the FileSystemEncoding, which would thus
|
||||
-- not roundtrip, as decodeBS always generates an output encoded that way.
|
||||
prop_b64_roundtrips :: TestableString -> Bool
|
||||
prop_b64_roundtrips ts
|
||||
| all (isAscii) s = s == decodeBS (fromB64' (toB64' (encodeBS s)))
|
||||
| otherwise = True
|
||||
where
|
||||
s = fromTestableString ts
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue