aboutsummaryrefslogtreecommitdiff
path: root/src/Data/Digest/Internal.chs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Data/Digest/Internal.chs')
-rw-r--r--src/Data/Digest/Internal.chs12
1 files changed, 2 insertions, 10 deletions
diff --git a/src/Data/Digest/Internal.chs b/src/Data/Digest/Internal.chs
index ed4e09e..86cea65 100644
--- a/src/Data/Digest/Internal.chs
+++ b/src/Data/Digest/Internal.chs
@@ -16,7 +16,6 @@
module Data.Digest.Internal where
-import Control.Exception (assert)
import Data.Bits (Bits((.&.)), shiftR)
import Data.ByteString (ByteString)
import qualified Data.ByteString as ByteString
@@ -27,12 +26,13 @@ import Data.Word (Word8)
import Foreign
(FinalizerPtr, ForeignPtr, Ptr, Storable(alignment, peek, sizeOf),
addForeignPtrFinalizer, alloca, allocaArray, mallocForeignPtr,
- nullPtr, throwIf_, withForeignPtr)
+ nullPtr, withForeignPtr)
import Foreign.C.Types
import Foreign.Marshal.Unsafe (unsafeLocalState)
import Unsafe.Coerce (unsafeCoerce)
import Foreign.Ptr.Cast (asVoidPtr)
+import Result
type LazyByteString = ByteString.Lazy.ByteString
@@ -70,11 +70,6 @@ evpMaxMdSize = {#const EVP_MAX_MD_SIZE#}
-- Some of these functions return 'CInt' even though they can never fail. Wrap
-- them to prevent warnings.
-alwaysSucceeds :: IO CInt -> IO ()
-alwaysSucceeds f = do
- r <- f
- assert (r == 1) (return ())
-
evpDigestUpdate :: Ptr EvpMdCtx -> Ptr a -> CULong -> IO ()
evpDigestUpdate ctx md bytes =
alwaysSucceeds $ {#call EVP_DigestUpdate as ^#} ctx (asVoidPtr md) bytes
@@ -85,9 +80,6 @@ evpDigestFinalEx ctx mdOut outSize =
-- Convert functions that can in fact fail to throw exceptions instead.
-requireSuccess :: IO CInt -> IO ()
-requireSuccess f = throwIf_ (/= 1) (const "BoringSSL failure") f
-
evpDigestInitEx :: Ptr EvpMdCtx -> Ptr EvpMd -> Ptr Engine -> IO ()
evpDigestInitEx ctx md engine =
requireSuccess $ {#call EVP_DigestInit_ex as ^#} ctx md engine