[Padding] add PKCS5/PKCS7 padding/unpadding methods

This commit is contained in:
Vincent Hanquez 2015-08-18 12:03:05 +01:00
parent 41c5af125c
commit cd8f70e062
4 changed files with 76 additions and 0 deletions

47
Crypto/Data/Padding.hs Normal file
View File

@ -0,0 +1,47 @@
-- |
-- Module : Crypto.Data.Padding
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
--
-- Various cryptographic padding commonly used for block ciphers
-- or assymetric systems.
--
module Crypto.Data.Padding
( Format(..)
, pad
, unpad
) where
import Data.ByteArray (ByteArray, Bytes)
import qualified Data.ByteArray as B
data Format =
PKCS5 -- ^ PKCS5: PKCS7 with hardcoded size of 8
| PKCS7 Int -- ^ PKCS7 with padding size between 1 and 255
deriving (Show, Eq)
-- | Apply some pad to a bytearray
pad :: ByteArray byteArray => Format -> byteArray -> byteArray
pad PKCS5 bin = pad (PKCS7 8) bin
pad (PKCS7 sz) bin = bin `B.append` paddingString
where
paddingString = B.replicate paddingByte (fromIntegral paddingByte)
paddingByte = sz - (B.length bin `mod` sz)
-- | Try to remove some padding from a bytearray.
unpad :: ByteArray byteArray => Format -> byteArray -> Maybe byteArray
unpad PKCS5 bin = unpad (PKCS7 8) bin
unpad (PKCS7 sz) bin
| len == 0 = Nothing
| (len `mod` sz) /= 0 = Nothing
| paddingSz < 1 || paddingSz > len = Nothing
| paddingWitness `B.constEq` padding = Just content
| otherwise = Nothing
where
len = B.length bin
paddingByte = B.index bin (len - 1)
paddingSz = fromIntegral paddingByte
(content, padding) = B.splitAt (len - paddingSz) bin
paddingWitness = B.replicate paddingSz paddingByte :: Bytes

View File

@ -83,6 +83,7 @@ Library
Crypto.Cipher.TripleDES
Crypto.Cipher.Types
Crypto.Data.AFIS
Crypto.Data.Padding
Crypto.Error
Crypto.MAC.Poly1305
Crypto.MAC.HMAC

26
tests/Padding.hs Normal file
View File

@ -0,0 +1,26 @@
{-# LANGUAGE OverloadedStrings #-}
module Padding (tests) where
import qualified Data.ByteString as B
import Imports
import Crypto.Error
import Crypto.Data.Padding
cases =
[ ("abcdef", 8, "abcdef\x02\x02")
, ("abcd", 4, "abcd\x04\x04\x04\x04")
, ("xyze", 5, "xyze\x01")
]
--instance Arbitrary where
testPad :: Int -> (B.ByteString, Int, B.ByteString) -> TestTree
testPad n (inp, sz, padded) =
testCase (show n) $ propertyHoldCase [ eqTest "padded" padded (pad (PKCS7 sz) inp)
, eqTest "unpadded" (Just inp) (unpad (PKCS7 sz) padded)
]
tests = testGroup "Padding"
[ testGroup "Cases" $ map (uncurry testPad) (zip [1..] cases)
]

View File

@ -24,10 +24,12 @@ import qualified KAT_RC4
import qualified KAT_TripleDES
-- misc --------------------------------
import qualified KAT_AFIS
import qualified Padding
tests = testGroup "cryptonite"
[ Number.tests
, Hash.tests
, Padding.tests
, testGroup "MAC"
[ Poly1305.tests
, KAT_HMAC.tests