aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorAlbert Krewinkel <[email protected]>2024-09-29 18:32:12 +0200
committerAlbert Krewinkel <[email protected]>2024-09-29 18:36:56 +0200
commit7565a90cec79c5fcd1d3b3e5ddb042d2cdaccac3 (patch)
treef48f1ff5d8c87092990c97ff4b9aa068501304c7
parent7a96b253c205a1cf5dad862a46e29f0183d36cc7 (diff)
Stop depending on package SHA
Pandoc already depends on `crypton-conntection`, and thus transitively on `crypton`. The latter provides a vast variety of hashing algorithms and makes the dependency on SHA unnecessary.
-rw-r--r--pandoc-lua-engine/pandoc-lua-engine.cabal4
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Utils.hs7
-rw-r--r--pandoc.cabal2
-rw-r--r--src/Text/Pandoc/MediaBag.hs7
-rw-r--r--src/Text/Pandoc/PDF.hs8
-rw-r--r--src/Text/Pandoc/Readers/Ipynb.hs14
-rw-r--r--src/Text/Pandoc/Readers/RTF.hs4
-rw-r--r--src/Text/Pandoc/SelfContained.hs5
-rw-r--r--src/Text/Pandoc/Writers/Docx/OpenXML.hs7
9 files changed, 27 insertions, 31 deletions
diff --git a/pandoc-lua-engine/pandoc-lua-engine.cabal b/pandoc-lua-engine/pandoc-lua-engine.cabal
index 93ca4c935..a9ff59186 100644
--- a/pandoc-lua-engine/pandoc-lua-engine.cabal
+++ b/pandoc-lua-engine/pandoc-lua-engine.cabal
@@ -105,9 +105,9 @@ library
, Text.Pandoc.Lua.Writer.Classic
, Text.Pandoc.Lua.Writer.Scaffolding
- build-depends: SHA >= 1.6 && < 1.7
- , aeson
+ build-depends: aeson
, bytestring >= 0.9 && < 0.13
+ , crypton >= 0.30 && < 1.1
, citeproc >= 0.8 && < 0.9
, containers >= 0.6.0.1 && < 0.8
, data-default >= 0.4 && < 0.8
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Utils.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Utils.hs
index 8bd04b72b..325f09258 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Utils.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Utils.hs
@@ -19,6 +19,7 @@ module Text.Pandoc.Lua.Module.Utils
import Control.Applicative ((<|>))
import Control.Monad ((<$!>))
+import Crypto.Hash (hashWith, SHA1(SHA1))
import Data.Data (showConstr, toConstr)
import Data.Default (def)
import Data.Maybe (fromMaybe)
@@ -34,8 +35,6 @@ import Text.Pandoc.Lua.Marshal.AST
import Text.Pandoc.Lua.Marshal.Reference
import Text.Pandoc.Lua.PandocLua (PandocLua (unPandocLua))
-import qualified Data.Digest.Pure.SHA as SHA
-import qualified Data.ByteString.Lazy as BSL
import qualified Data.Map as Map
import qualified Data.Text as T
import qualified Text.Pandoc.Builder as B
@@ -301,8 +300,8 @@ run_json_filter = defun "run_json_filter"
-- | Documented Lua function to compute the hash of a string.
sha1 :: DocumentedFunction e
sha1 = defun "sha1"
- ### liftPure (SHA.showDigest . SHA.sha1)
- <#> parameter (fmap BSL.fromStrict . peekByteString) "string" "input" ""
+ ### liftPure (show . hashWith SHA1)
+ <#> parameter peekByteString "string" "input" ""
=#> functionResult pushString "string" "hexadecimal hash value"
#? "Computes the SHA1 hash of the given string input."
diff --git a/pandoc.cabal b/pandoc.cabal
index 838ad674e..b164c61e4 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -472,7 +472,6 @@ library
build-depends: xml-light,
Glob >= 0.7 && < 0.11,
JuicyPixels >= 3.1.6.1 && < 3.4,
- SHA >= 1.6 && < 1.7,
aeson >= 2.0.1.0 && < 2.3,
aeson-pretty >= 0.8.9 && < 0.9,
array >= 0.5 && < 0.6,
@@ -488,6 +487,7 @@ library
commonmark-extensions >= 0.2.5.5 && < 0.3,
commonmark-pandoc >= 0.2.2.1 && < 0.3,
containers >= 0.6.0.1 && < 0.8,
+ crypton >= 0.30 && < 1.1,
crypton-connection >= 0.3.1 && < 0.5,
data-default >= 0.4 && < 0.8,
deepseq >= 1.3 && < 1.6,
diff --git a/src/Text/Pandoc/MediaBag.hs b/src/Text/Pandoc/MediaBag.hs
index 528500877..1afc49a9b 100644
--- a/src/Text/Pandoc/MediaBag.hs
+++ b/src/Text/Pandoc/MediaBag.hs
@@ -23,20 +23,19 @@ module Text.Pandoc.MediaBag (
mediaDirectory,
mediaItems
) where
+import Crypto.Hash (hashWith, SHA1(SHA1))
import qualified Data.ByteString.Lazy as BL
import Data.Data (Data)
import qualified Data.Map as M
import Data.Maybe (fromMaybe, isNothing)
import Data.Typeable (Typeable)
-import Network.URI (unEscapeString)
import System.FilePath
import qualified System.FilePath.Posix as Posix
import qualified System.FilePath.Windows as Windows
import Text.Pandoc.MIME (MimeType, getMimeTypeDef, extensionFromMimeType)
import Data.Text (Text)
import qualified Data.Text as T
-import Data.Digest.Pure.SHA (sha1, showDigest)
-import Network.URI (URI (..), parseURI, isURI)
+import Network.URI (URI (..), isURI, parseURI, unEscapeString)
import Data.List (isInfixOf)
data MediaItem =
@@ -92,7 +91,7 @@ insertMedia fp mbMime contents (MediaBag mediamap) =
&& not (".." `isInfixOf` fp'')
&& '%' `notElem` fp''
then fp''
- else showDigest (sha1 contents) <> ext
+ else show (hashWith SHA1 $ BL.toStrict contents) <> ext
fallback = case takeExtension fp'' of
".gz" -> getMimeTypeDef $ dropExtension fp''
_ -> getMimeTypeDef fp''
diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs
index b97c73eff..dc5e9435f 100644
--- a/src/Text/Pandoc/PDF.hs
+++ b/src/Text/Pandoc/PDF.hs
@@ -20,6 +20,7 @@ import qualified Codec.Picture as JP
import qualified Control.Exception as E
import Control.Monad.Trans (MonadIO (..))
import Control.Monad (foldM_)
+import Crypto.Hash (hashWith, SHA1(SHA1))
import qualified Data.ByteString as BS
import Data.ByteString.Lazy (ByteString)
import qualified Data.ByteString.Lazy as BL
@@ -52,7 +53,6 @@ import qualified Text.Pandoc.UTF8 as UTF8
import Text.Pandoc.Walk (walkM)
import Text.Pandoc.Writers.Shared (getField, metaToContext)
import Control.Monad.Catch (MonadMask)
-import Data.Digest.Pure.SHA (sha1, showDigest)
#ifdef _WINDOWS
import Data.List (intercalate)
#endif
@@ -236,7 +236,7 @@ convertImage opts tmpdir fname = do
E.catch (Right pngOut <$ JP.savePngImage pngOut img) $
\(e :: E.SomeException) -> return (Left (tshow e))
where
- sha = showDigest (sha1 (UTF8.fromStringLazy fname))
+ sha = show (hashWith SHA1 (UTF8.fromString fname))
pngOut = normalise $ tmpdir </> sha <.> "png"
pdfOut = normalise $ tmpdir </> sha <.> "pdf"
svgIn = normalise fname
@@ -434,8 +434,8 @@ runTeXProgram program args tmpDir outDir = do
tocFileExists <- fileExists tocFile
if tocFileExists
then do
- tocContents <- BL.fromStrict <$> readFileStrict tocFile
- pure $ Just $! sha1 tocContents
+ tocContents <- readFileStrict tocFile
+ pure $ Just $! hashWith SHA1 tocContents
else pure Nothing
-- compare hash of toc to former hash to see if it changed (#9295)
let rerunWarnings' = rerunWarnings ++
diff --git a/src/Text/Pandoc/Readers/Ipynb.hs b/src/Text/Pandoc/Readers/Ipynb.hs
index a6a14be99..084b69b6b 100644
--- a/src/Text/Pandoc/Readers/Ipynb.hs
+++ b/src/Text/Pandoc/Readers/Ipynb.hs
@@ -15,9 +15,9 @@ Ipynb (Jupyter notebook JSON format) reader for pandoc.
-}
module Text.Pandoc.Readers.Ipynb ( readIpynb )
where
+import Crypto.Hash (hashWith, SHA1(SHA1))
import Data.Char (isDigit)
import Data.Maybe (fromMaybe)
-import Data.Digest.Pure.SHA (sha1, showDigest)
import Text.Pandoc.Options
import Control.Applicative ((<|>))
import qualified Data.Scientific as Scientific
@@ -186,16 +186,16 @@ handleData (JSONMeta metadata) (MimeBundle mb) =
Error _ -> mempty
_ -> mempty
let metaPairs = jsonMetaToPairs meta
- let bl = case d of
- BinaryData bs -> BL.fromStrict bs
- TextualData t -> BL.fromStrict $ UTF8.fromText t
- JsonData v -> encode v
+ let bs = case d of
+ BinaryData bs' -> bs'
+ TextualData t -> UTF8.fromText t
+ JsonData v -> BL.toStrict $ encode v
-- SHA1 hash for filename
- let fname = T.pack (showDigest (sha1 bl)) <>
+ let fname = T.pack (show (hashWith SHA1 bs)) <>
case extensionFromMimeType mt of
Nothing -> ""
Just ext -> "." <> ext
- insertMedia (T.unpack fname) (Just mt) bl
+ insertMedia (T.unpack fname) (Just mt) (BL.fromStrict bs)
return $ B.para $ B.imageWith ("",[],metaPairs) fname "" mempty
dataBlock ("text/html", TextualData t)
diff --git a/src/Text/Pandoc/Readers/RTF.hs b/src/Text/Pandoc/Readers/RTF.hs
index 7e1a779d0..52c549c75 100644
--- a/src/Text/Pandoc/Readers/RTF.hs
+++ b/src/Text/Pandoc/Readers/RTF.hs
@@ -19,6 +19,7 @@ import qualified Data.IntMap as IntMap
import qualified Data.Sequence as Seq
import Control.Monad
import Control.Monad.Except (throwError)
+import Crypto.Hash (hashWith, SHA1(SHA1))
import Data.List (find, foldl')
import Data.Word (Word8, Word16)
import Data.Default
@@ -35,7 +36,6 @@ import Text.Pandoc.Logging (LogMessage(UnsupportedCodePage))
import Text.Pandoc.Shared (tshow)
import Data.Char (isAlphaNum, chr, isAscii, isLetter, isSpace, ord)
import qualified Data.ByteString.Lazy as BL
-import Data.Digest.Pure.SHA (sha1, showDigest)
import Data.Maybe (mapMaybe, fromMaybe)
import Safe (lastMay, initSafe, headDef)
-- import Debug.Trace
@@ -920,7 +920,7 @@ handlePict toks = do
Nothing -> (Nothing, "")
case mimetype of
Just mt -> do
- let pictname = showDigest (sha1 bytes) <> ext
+ let pictname = show (hashWith SHA1 $ BL.toStrict bytes) <> ext
insertMedia pictname (Just mt) bytes
modifyGroup $ \g -> g{ gImage = Just pict{ picName = T.pack pictname,
picBytes = bytes } }
diff --git a/src/Text/Pandoc/SelfContained.hs b/src/Text/Pandoc/SelfContained.hs
index 03dddc596..617cdfc33 100644
--- a/src/Text/Pandoc/SelfContained.hs
+++ b/src/Text/Pandoc/SelfContained.hs
@@ -24,7 +24,7 @@ import qualified Data.ByteString.Char8 as B
import qualified Data.ByteString.Lazy as L
import qualified Data.Text as T
import Data.Char (isAlphaNum, isAscii)
-import Data.Digest.Pure.SHA (sha1, showDigest)
+import Crypto.Hash (hashWith, SHA1(SHA1))
import Network.URI (escapeURIString)
import System.FilePath (takeDirectory, takeExtension, (</>))
import Text.HTML.TagSoup
@@ -216,8 +216,7 @@ convertTags (t@(TagOpen tagname as):ts)
Fetched ("image/svg+xml", bs) | inlineSvgs -> do
-- we filter CR in the hash to ensure that Windows
-- and non-Windows tests agree:
- let hash = T.pack $ take 20 $ showDigest $
- sha1 $ L.fromStrict
+ let hash = T.pack $ take 20 $ show $ hashWith SHA1
$ B.filter (/='\r') bs
return $ Left (hash, getSvgTags (toText bs))
Fetched (mt,bs) -> return $ Right (x, makeDataURI (mt,bs))
diff --git a/src/Text/Pandoc/Writers/Docx/OpenXML.hs b/src/Text/Pandoc/Writers/Docx/OpenXML.hs
index d98ef5d30..bbd7d730e 100644
--- a/src/Text/Pandoc/Writers/Docx/OpenXML.hs
+++ b/src/Text/Pandoc/Writers/Docx/OpenXML.hs
@@ -23,6 +23,7 @@ module Text.Pandoc.Writers.Docx.OpenXML ( writeOpenXML, maxListLevel ) where
import Control.Monad (when, unless)
import Control.Applicative ((<|>))
import Control.Monad.Except (catchError)
+import Crypto.Hash (hashWith, SHA1(SHA1))
import qualified Data.ByteString.Lazy as BL
import Data.Char (isLetter, isSpace)
import Text.Pandoc.Char (isCJK)
@@ -35,8 +36,6 @@ import Control.Monad.Reader ( asks, MonadReader(local) )
import qualified Data.Set as Set
import qualified Data.Text as T
import Data.Text (Text)
-import qualified Data.Text.Lazy as TL
-import Data.Digest.Pure.SHA (sha1, showDigest)
import Skylighting
import Text.DocLayout (hcat, vcat, literal, render)
import Text.Pandoc.Class (PandocMonad, report, getMediaBag)
@@ -45,7 +44,7 @@ import Text.Pandoc.MediaBag (lookupMedia, MediaItem(..))
import qualified Text.Pandoc.Translations as Term
import qualified Text.Pandoc.Class.PandocMonad as P
import qualified Text.Pandoc.Builder as B
-import Text.Pandoc.UTF8 (fromTextLazy)
+import Text.Pandoc.UTF8 (fromText)
import Text.Pandoc.Definition
import Text.Pandoc.Highlighting (highlight)
import Text.Pandoc.Templates (compileDefaultTemplate, renderTemplate)
@@ -1082,7 +1081,7 @@ toBookmarkName s
| Just (c, _) <- T.uncons s
, isLetter c
, T.length s <= 40 = s
- | otherwise = T.pack $ 'X' : drop 1 (showDigest (sha1 (fromTextLazy $ TL.fromStrict s)))
+ | otherwise = T.pack $ 'X' : drop 1 (show (hashWith SHA1 (fromText s)))
maxListLevel :: Int
maxListLevel = 8