summaryrefslogtreecommitdiff
path: root/Crypto
diff options
context:
space:
mode:
authorjoe <joe@jerkface.net>2016-08-26 03:10:40 -0400
committerJoe Crayne <joe@jerkface.net>2019-07-01 09:19:55 -0400
commit39d8a08aad1d2dd48b807ab867aa17475e4278c4 (patch)
treebd3146dacd3d57b123dd172e4901c61014ea3db9 /Crypto
parenta90b1f609d8a559694ad31ea0b28ec6309a8b661 (diff)
Completed cryptonite support.
Diffstat (limited to 'Crypto')
-rw-r--r--Crypto/Cipher/Cast5.hs2
-rw-r--r--Crypto/Cipher/ThomasToVincent.hs25
2 files changed, 24 insertions, 3 deletions
diff --git a/Crypto/Cipher/Cast5.hs b/Crypto/Cipher/Cast5.hs
index dfd30c7..da9d109 100644
--- a/Crypto/Cipher/Cast5.hs
+++ b/Crypto/Cipher/Cast5.hs
@@ -83,7 +83,7 @@ instance Cast5Bits size => Serialize (Cast5 size) where
83 83
84-- instance Cast5Bits size => BlockCipher (Cast5 size) where 84-- instance Cast5Bits size => BlockCipher (Cast5 size) where
85blockSize :: forall size. Cast5Bits size => Tagged (Cast5 size) Int 85blockSize :: forall size. Cast5Bits size => Tagged (Cast5 size) Int
86blockSize = Tagged 64 86blockSize = Tagged 64 -- bits
87 87
88encryptBlock :: forall size. Cast5Bits size => Cast5 size -> S.ByteString -> S.ByteString 88encryptBlock :: forall size. Cast5Bits size => Cast5 size -> S.ByteString -> S.ByteString
89encryptBlock (Cast5 subkeys fs _ _ key) = 89encryptBlock (Cast5 subkeys fs _ _ key) =
diff --git a/Crypto/Cipher/ThomasToVincent.hs b/Crypto/Cipher/ThomasToVincent.hs
index 5a68cf3..cf5cdee 100644
--- a/Crypto/Cipher/ThomasToVincent.hs
+++ b/Crypto/Cipher/ThomasToVincent.hs
@@ -5,7 +5,12 @@ module Crypto.Cipher.ThomasToVincent where
5import qualified Data.ByteString as S 5import qualified Data.ByteString as S
6import Crypto.Cipher.Types 6import Crypto.Cipher.Types
7import Crypto.Cipher.Cast5 7import Crypto.Cipher.Cast5
8#if defined(VERSION_cryptonite)
9import qualified Data.ByteArray as Bytes
10import Crypto.Error
11#else
8import Data.Byteable 12import Data.Byteable
13#endif
9 14
10import Data.Tagged 15import Data.Tagged
11{- 16{-
@@ -19,9 +24,14 @@ endif
19type ThomasToVincent b = b 24type ThomasToVincent b = b
20 25
21instance Cast5Bits size => Cipher (Cast5 size) where 26instance Cast5Bits size => Cipher (Cast5 size) where
22 cipherName _ = "CAST-5" 27 cipherName _ = "CAST-"++show (cast5bits (undefined :: size))
28#if defined(VERSION_cryptonite)
29 cipherInit k = CryptoPassed b
30 where Just b = buildKey (Bytes.convert k)
31#else
23 cipherInit k = b 32 cipherInit k = b
24 where Just b = buildKey (toBytes k) 33 where Just b = buildKey (toBytes k)
34#endif
25 cipherKeySize _ = KeySizeFixed (bitlen `div` 8) 35 cipherKeySize _ = KeySizeFixed (bitlen `div` 8)
26 where Tagged bitlen = keyLength :: Tagged (Cast5 size) Int 36 where Tagged bitlen = keyLength :: Tagged (Cast5 size) Int
27 37
@@ -42,14 +52,25 @@ instance Cast5Bits size => BlockCipher (Cast5 size) where
42 blockSize _ = bitlen `div` 8 52 blockSize _ = bitlen `div` 8
43 where Tagged bitlen = Crypto.Cipher.Cast5.blockSize :: Tagged (Cast5 size) Int 53 where Tagged bitlen = Crypto.Cipher.Cast5.blockSize :: Tagged (Cast5 size) Int
44 54
55 -- ecbEncrypt :: (BlockCipher cipher, ByteArray ba) => cipher -> ba -> ba
45 -- modeEcb' :: BlockCipher k => k -> B.ByteString -> B.ByteString 56 -- modeEcb' :: BlockCipher k => k -> B.ByteString -> B.ByteString
46 ecbEncrypt k msg = 57 ecbEncrypt k msg =
47 let chunks = chunkFor' k msg 58#if defined(VERSION_cryptonite)
59 let chunks = chunkFor' k $ Bytes.convert msg
60 in Bytes.convert $ S.concat $ map (encryptBlock k) chunks
61#else
62 let chunks = chunkFor' k $ msg
48 in S.concat $ map (encryptBlock k) chunks 63 in S.concat $ map (encryptBlock k) chunks
64#endif
49 65
50 ecbDecrypt k ct = 66 ecbDecrypt k ct =
67#if defined(VERSION_cryptonite)
68 let chunks = chunkFor' k $ Bytes.convert ct
69 in Bytes.convert $ S.concat $ map (decryptBlock k) chunks
70#else
51 let chunks = chunkFor' k ct 71 let chunks = chunkFor' k ct
52 in S.concat $ map (decryptBlock k) chunks 72 in S.concat $ map (decryptBlock k) chunks
73#endif
53 74
54 75
55{- 76{-