2017-05-12 27 views
1

以下步驟描述了在Jeff Moser's popular tutorial中的關鍵擴展,我已經編寫了用於密鑰擴展的代碼。這裏是整個文件(它也計算S-Box),所以人們可以編譯和嘗試它。Haskell AES密鑰擴展有什麼問題?

{-# LANGUAGE NoMonomorphismRestriction #-} 

import Control.Applicative (liftA2) 
import Data.Bits (xor, shiftL, shiftR, (.|.), (.&.)) 
import Data.List (transpose, sortBy) 
import Data.Ord (comparing) 
import Data.Word (Word8) 
import Numeric (showHex) 

keys = f 16 $ f 8 $ f 4 $ f 2 $ f 1 key 
where 
    f w n = xpndC . xpndB . xpndA $ xpndD w n 

xpndC :: [[Word8]] -> [[Word8]] 
xpndC ws = transpose [head ws, b, zipWith xor b c, last ws] 
where 
    (b,c) = (ws !! 1, ws !! 2) 

xpndB :: [[Word8]] -> [[Word8]] 
xpndB ws = a : zipWith xor a b : drop 2 ws 
where 
    (a,b) = (head ws, ws !! 1) 

xpndA :: [[Word8]] -> [[Word8]] 
xpndA ws = zipWith xor a d : tail ws 
where 
    (a,d) = (head ws, last ws) 

xpndD rc ws = take 3 tW ++ [w'] 
where 
    w' = zipWith xor (map sub w) [rc, 0, 0, 0] 
    tW = transpose ws 
    w = take 4 $ tail $ cycle $ last tW 

-------------------------------------------------------------- 
sub w = get sbox (fromIntegral lo) $ fromIntegral hi 
where 
    (hi, lo) = nibs w 

get wss x y = (wss !! y) !! x 

print' = print . w128 . concat . transpose 
where 
    w128 = concatMap (f . (`showHex` "")) 
    f w = (length w < 2) ? (' ':'0':w, ' ':w) 

grid _ [] = [] 
grid n xs = take n xs : grid n (drop n xs) 

nibs w = (shiftR (w .&. 0xF0) 4, w .&. 0x0F) 
(⊕)  = xor 
p ? (a,b) = if p then a else b; infix 2 ? 

--------------------------------------------------- 
sbox :: [[Word8]] 
sbox = grid 16 $ map snd $ sortBy (comparing fst) $ sbx 1 1 [] 

sbx :: Word8 -> Word8 -> [(Word8, Word8)] -> [(Word8, Word8)] 
sbx p q ws 
    | length ws == 255 = (0, 0x63) : ws 
    | otherwise = sbx p' r $ (p', xf ⊕ 0x63) : ws 
where 
    p' = p ⊕ shiftL p 1 ⊕ ((p .&. 0x80 /= 0) ? (0x1B, 0)) 
    q1 = foldl (liftA2 (.) xor shiftL) q [1, 2, 4] 
    r = q1 ⊕ ((q1 .&. 0x80 /= 0) ? (0x09, 0)) 
    xf = r ⊕ rotl8 r 1 ⊕ rotl8 r 2 ⊕ rotl8 r 3 ⊕ rotl8 r 4 

rotl8 w n = (w `shiftL` n) .|. (w `shiftR` (8 - n)) 

key = [[0,0,0,0], 
     [0,0,0,0], 
     [0,0,0,0], 
     [0,0,0,0]] :: [[Word8]] 

當我測試針對全零測試關鍵這段代碼,它公佈的預期相匹配的第四次迭代:ee 06 da 7b 87 6a 15 81 75 9e 42 b2 7e 91 ee 2b

但是,當我嘗試下一次迭代:keys = f 16 $ f 8 $ f 4 $ f 2 $ f 1, 結果的最後32位是錯誤的:7f 2e 2b 88 f8 44 3e 09 8d da 7c bb 91 28 f1 f3

當我使用全部0xFF作爲初始密鑰時,會發生同樣的行爲 - 最後32位錯誤。在後續的迭代中,所有的位都是錯誤的。

如果我使用測試矢量00 01 02 03 04 05 06 07 08 09 0a 0b 0c 0d 0e 0f,事情出錯得快得多 - 我開始在第二次迭代中出錯位。

這是怎麼回事?我注意到Moser先生在部分2b中寫道:4xor第一列的上一輪密鑰 - 但是沒有前一輪的初始密鑰,所以這讓我很困惑。這是我做錯了什麼?

僅供參考,here are the test vectors.

+2

你能產生一個完整,編譯,測試案例?碎片在這裏不是很有幫助。 –

+0

高興!我已經添加了一個編譯和演示問題的最小版本。 – sacheie

回答

3

你缺少一個步驟。

xpndC ws = transpose [head ws, b, zipWith xor b c, last ws] 

第四列應該是前一列的第四列(在第一列中丟棄)和新的第三列。

事實上,xor x x = 0以某種方式促成了這種錯誤只有在第五次迭代才引人注目。在固定結構上


次要文體評論

模式匹配比(!!)少彆扭。

xpndC :: [[Word8]] -> [[Word8]] 
xpndC [a,b,c,d] = [a, b, zipWith xor b c, d] 

還要注意的是,步驟2b43實際上掃描。粗略地說,它結束了看起來像這樣(與你的最後一個環節借用名字schedule_core):

new = tail $ scanl (zipWith xor) (schedule_core (last old)) old 

編輯:修復

解決方案本質上是扔掉的最後一列。您可以爲速戰速決,這樣注入它的一個附加通:

keys = f 16 $ f 8 $ f 4 $ f 2 $ f 1 key 
where 
    f w n = xpndE (transpose n) . xpndC . xpndB . xpndA $ xpndD w n 

xpndE n [a,b,c,_] = transpose [a,b,c,zipWith xor c (last n)] 

xpndC = (...) {- remove transpose here -} 

xpnd*功能可能有點過於細粒度,一旦你意識到這個列表是相當小的。如果您想保留它,我也會將transpose排除在外。

keys = transpose $ f 16 $ f 8 $ f 4 $ f 2 $ f 1 $ transpose key 
    where 
    f rc [a, b, c, d] = 
     let e = schedule rc d 
      a' = zipWith xor a e 
      b' = zipWith xor b a' 
      c' = zipWith xor c b' 
      d' = zipWith xor c c' 
     in [a', b', c', d'] -- Here is where one may recognize `scanl` or a fold. 

至於schedule,那就是需要的最後一列(d以上,last tW下文),並加擾它的函數(e以上,w'下文)。您可以從您的xpndD定義解壓:

xpndD rc ws = take 3 tW ++ [w'] 
where 
    w' = zipWith xor (map sub w) [rc, 0, 0, 0] 
    tW = transpose ws 
    w = take 4 $ tail $ cycle $ last tW 

我們得到(模純化妝品改寫take 4 $ tail $ cycle d = tail d ++ [head d]):

schedule rc d = zipWith xor (map sub $ tail d ++ [head d]) [rc, 0, 0, 0] 
+0

感謝您對模式匹配的提示......但是您能否詳細說明我應該如何重新定義'xpndC',如果我已經丟掉列,我應該用'xor'第四列? 我也喜歡使用'scanl',但我無法弄清楚如何將'schedule_core'的C代碼翻譯成Haskell。我知道這很重要,但我可以在上下文中看到這些想法?我得到的印象是不必要的重構。 – sacheie

+0

一個奇妙的答案 - 我特別感謝除了更優雅的掃描解釋之外的「快速修復」。謝謝! – sacheie

+0

很高興你喜歡它! –