Use base64 instead of base64-bytestring.

It is supposed to be faster and more standards-compliant.
This commit is contained in:
John MacFarlane 2022-08-14 10:40:22 -07:00
parent 2f5c75132a
commit 6625e9655e
6 changed files with 11 additions and 13 deletions

View file

@ -474,7 +474,6 @@ library
aeson-pretty >= 0.8.9 && < 0.9,
array >= 0.5 && < 0.6,
attoparsec >= 0.12 && < 0.15,
base64-bytestring >= 0.1 && < 1.3,
binary >= 0.7 && < 0.11,
blaze-html >= 0.9 && < 0.10,
blaze-markup >= 0.8 && < 0.9,
@ -491,6 +490,7 @@ library
directory >= 1.2.3 && < 1.4,
doclayout >= 0.4 && < 0.5,
doctemplates >= 0.10 && < 0.11,
base64 >= 0.4 && < 0.5,
emojis >= 0.1 && < 0.2,
exceptions >= 0.8 && < 0.11,
file-embed >= 0.0 && < 0.1,

View file

@ -36,7 +36,7 @@ module Text.Pandoc.Class.IO
import Control.Monad.Except (throwError)
import Control.Monad.IO.Class (MonadIO, liftIO)
import Data.ByteString.Base64 (decodeLenient)
import Data.ByteString.Base64.URL (decodeBase64Lenient)
import Data.ByteString.Lazy (toChunks)
import Data.Text (Text, pack, unpack)
import Data.Time (TimeZone, UTCTime)
@ -125,7 +125,7 @@ openURL u
let mime = T.takeWhile (/=',') u''
let contents = UTF8.fromString $
unEscapeString $ T.unpack $ T.drop 1 $ T.dropWhile (/=',') u''
return (decodeLenient contents, Just mime)
return (decodeBase64Lenient contents, Just mime)
| otherwise = do
let toReqHeader (n, v) = (CI.mk (UTF8.fromText n), UTF8.fromText v)
customHeaders <- map toReqHeader <$> getsCommonState stRequestHeaders

View file

@ -25,7 +25,7 @@ TODO:
module Text.Pandoc.Readers.FB2 ( readFB2 ) where
import Control.Monad.Except (throwError)
import Control.Monad.State.Strict
import Data.ByteString.Base64.Lazy
import Data.ByteString.Lazy.Base64.URL
import Data.Functor
import Data.List (intersperse)
import qualified Data.Map as M
@ -202,7 +202,7 @@ parseBinaryElement e =
report $ IgnoredElement "binary without content-type attribute"
(Just filename, contentType) ->
insertMedia (T.unpack filename) contentType
(decodeLenient
(decodeBase64Lenient
(UTF8.fromTextLazy . TL.fromStrict . strContent $ e))
-- * Type parsers

View file

@ -27,7 +27,7 @@ import Control.Applicative ((<|>))
import Control.Monad (guard, msum, mzero, unless, void)
import Control.Monad.Except (throwError, catchError)
import Control.Monad.Reader (ask, asks, lift, local, runReaderT)
import Data.ByteString.Base64 (encode)
import Data.Text.Encoding.Base64.URL (encodeBase64)
import Data.Char (isAlphaNum, isLetter)
import Data.Default (Default (..), def)
import Data.Foldable (for_)
@ -785,8 +785,7 @@ pSvg = do
contents <- many (notFollowedBy (pCloses "svg") >> pAny)
closet <- TagClose "svg" <$ (pCloses "svg" <|> eof)
let rawText = T.strip $ renderTags' (opent : contents ++ [closet])
let svgData = "data:image/svg+xml;base64," <>
UTF8.toText (encode $ UTF8.fromText rawText)
let svgData = "data:image/svg+xml;base64," <> encodeBase64 rawText
return $ B.imageWith (ident,cls,[]) svgData mempty mempty
pCodeWithClass :: PandocMonad m => Text -> Text -> TagParser m Inlines

View file

@ -19,7 +19,7 @@ import Codec.Compression.GZip as Gzip
import Control.Applicative ((<|>))
import Control.Monad.Trans (lift)
import Data.ByteString (ByteString)
import Data.ByteString.Base64
import Data.ByteString.Base64.URL (encodeBase64)
import qualified Data.ByteString.Char8 as B
import qualified Data.ByteString.Lazy as L
import qualified Data.Text as T
@ -45,7 +45,7 @@ makeDataURI :: (MimeType, ByteString) -> T.Text
makeDataURI (mime, raw) =
if textual
then "data:" <> mime' <> "," <> T.pack (escapeURIString isOk (toString raw))
else "data:" <> mime' <> ";base64," <> toText (encode raw)
else "data:" <> mime' <> ";base64," <> encodeBase64 raw
where textual = "text/" `T.isPrefixOf` mime
mime' = if textual && T.any (== ';') mime
then mime <> ";charset=utf-8"

View file

@ -21,14 +21,13 @@ module Text.Pandoc.Writers.FB2 (writeFB2) where
import Control.Monad (zipWithM)
import Control.Monad.Except (catchError, throwError)
import Control.Monad.State.Strict (StateT, evalStateT, get, gets, lift, liftM, modify)
import Data.ByteString.Base64 (encode)
import Data.ByteString.Base64.URL (encodeBase64)
import Data.Char (isAscii, isControl, isSpace)
import Data.Either (lefts, rights)
import Data.List (intercalate)
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Encoding as TE
import Text.Pandoc.Network.HTTP (urlEncode)
import Text.Pandoc.XML.Light as X
@ -237,7 +236,7 @@ fetchImage href link = do
report $ CouldNotDetermineMimeType link
return Nothing
Just mime -> return $ Just (mime,
TE.decodeUtf8 $ encode bs))
encodeBase64 bs))
(\e ->
do report $ CouldNotFetchResource link (tshow e)
return Nothing)