Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
3 changes: 3 additions & 0 deletions botan-low/CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -42,6 +42,9 @@
* PATCH: fix an "insufficient buffer space" bug in
`Botan.Low.PubKey.Encrypt.encrypt` and `Botan.Low.PubKey.Decrypt.decrypt`. See
PR [#79](https://github.com/haskell-cryptography/botan/pull/79).
* PATCH: Fix an "insufficient buffer space" bug in
`Botan.Low.Cipher.cipherUpdate`. See PR
[#84](https://github.com/haskell-cryptography/botan/pull/84)

## 0.0.2.0 -- 2025-09-17

Expand Down
74 changes: 46 additions & 28 deletions botan-low/src/Botan/Low/Cipher.hs
Original file line number Diff line number Diff line change
Expand Up @@ -97,15 +97,14 @@ module Botan.Low.Cipher (

) where

import qualified Data.ByteString as ByteString

import Botan.Bindings.Cipher

import Botan.Low.BlockCipher
import Botan.Low.Error
import Botan.Low.Make
import Botan.Low.Prelude
import Botan.Low.Remake
import Data.Bits ((.&.))
import qualified Data.ByteString as ByteString

{- $introduction

Expand Down Expand Up @@ -442,31 +441,50 @@ cipherStart = mkWithObjectSetterCBytesLen withCipher botan_cipher_start
-- https://github.com/randombit/botan/blob/72dc18bbf598f2c3bef81a4fb2915e9c3c524ac4/src/lib/ffi/ffi_cipher.cpp#L133
--
-- Some ciphers (ChaChaPoly, EAX) may consume less input than the reported ideal granularity
cipherUpdate
:: Cipher -- ^ __cipher__
-> CipherUpdateFlags -- ^ __flags__
-> Int -- ^ __output_size__
-> ByteString -- ^ __input_bytes[]__
-> IO (Int,ByteString) -- ^ __(input_consumed,output[])__
cipherUpdate ctx flags outputSz input = withCipher ctx $ \ ctxPtr -> do
unsafeAsBytesLen input $ \ inputPtr inputSz -> do
alloca $ \ consumedPtr -> do
alloca $ \ writtenPtr -> do
output <- allocBytes outputSz $ \ outputPtr -> do
throwBotanIfNegative_ $ botan_cipher_update
ctxPtr
(fromIntegral flags)
outputPtr
(fromIntegral outputSz)
writtenPtr
(ConstPtr inputPtr)
inputSz
consumedPtr
consumed <- fromIntegral <$> peek consumedPtr
written <- fromIntegral <$> peek writtenPtr
-- NOTE: The safety of this function is suspect - may require deepseq
let processed = ByteString.take written output
in processed `seq` return (consumed,processed)
cipherUpdate ::
Cipher -- ^ __cipher__
-> CipherUpdateFlags -- ^ __flags__
-> Int -- ^ __output_size__
-> ByteString -- ^ __input_bytes[]__
-> IO (Int,ByteString) -- ^ __(input_consumed,output[])__
cipherUpdate ctx flags outputSz input =
withCipher ctx $ \ ctxPtr ->
unsafeAsBytesLen input $ \ inputPtr inputSz ->
alloca $ \ consumedPtr ->
alloca $ \ writtenPtr -> do
eithOutput <-
try $ allocBytes outputSz $ \ outputPtr ->do
throwBotanIfNegative_ $ botan_cipher_update
ctxPtr
(fromIntegral flags)
outputPtr
(fromIntegral outputSz)
writtenPtr
(ConstPtr inputPtr)
inputSz
consumedPtr
-- If inssuficient buffer space, try again
output <- case eithOutput of
Left InsufficientBufferSpaceException{} -> do
outputSz' <- peek writtenPtr
allocBytes (fromIntegral outputSz') $ \ outputPtr ->do
throwBotanIfNegative_ $ botan_cipher_update
ctxPtr
(fromIntegral flags)
outputPtr
outputSz'
writtenPtr
(ConstPtr inputPtr)
-- No input should be provided on the second try if the first
-- try had the FINAL flag set
(if flags .&. BOTAN_CIPHER_UPDATE_FLAG_FINAL /= 0 then 0 else inputSz)
consumedPtr
Right bs -> pure bs
consumed <- fromIntegral <$> peek consumedPtr
written <- fromIntegral <$> peek writtenPtr
-- NOTE: The safety of this function is suspect - may require deepseq
let processed = ByteString.take written output
in processed `seq` return (consumed,processed)

{- |
Encrypt and finalize a complete piece of data.
Expand Down
28 changes: 21 additions & 7 deletions botan-low/test/Test/Botan/Low/Cipher.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,9 +3,14 @@

module Test.Botan.Low.Cipher (tests) where

import Botan.Bindings.Version (botan_version_major,
botan_version_minor)
import Botan.Low.Cipher
import Botan.Low.RNG
import Control.Monad
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import System.IO.Unsafe (unsafePerformIO)
import Test.Hspec
import Test.Tasty
import Test.Tasty.Hspec
Expand All @@ -17,13 +22,25 @@ tests = do
specs <- testSpec "spec_cipher" spec_cipher
pure $ testGroup "Test.Botan.Low.Cipher" [
specs
-- TODO: temporarily disabled because the test suite fails. See issue
-- #33.
| False
]

testModes :: [ByteString]
testModes = filter p (cipherModes ++ aeads)
where
p s
-- TODO: also test "Lion" and "Cascade"
| "Lion" `BS.isPrefixOf` s || "Cascade" `BS.isPrefixOf` s
= False
-- SIV and CCM have bugs on versions earlier than 3.5
| unsafePerformIO botan_version_major == 3
, unsafePerformIO botan_version_minor <= 4
, "SIV" `BS.isSuffixOf` s || "CCM" `BS.isSuffixOf` s
= False
| otherwise
= True

spec_cipher :: Spec
spec_cipher = testSuite (cipherModes ++ aeads) chars $ \ cipher -> do
spec_cipher = testSuite testModes chars $ \ cipher -> do
it "can initialize a cipher encryption context" $ do
_ctx <- cipherInit cipher Encrypt
pass
Expand Down Expand Up @@ -221,10 +238,7 @@ spec_cipher = testSuite (cipherModes ++ aeads) chars $ \ cipher -> do
cipherStart offlinectx n
g <- cipherGetIdealUpdateGranularity onlinectx
msg <- systemRNGGet (8 * g)
putStrLn " Testing online encryption:"
onlinemsg <- cipherEncryptOnline onlinectx msg
putStrLn " Testing offline encryption:"
offlinemsg <- cipherEncrypt offlinectx msg
putStrLn " Result:"
onlinemsg `shouldBe` offlinemsg
pass