On Wed, Sep 21, 2011 at 2:29 AM, Vincent Hanquez <t...@snarc.org> wrote:
> Hi Felipe,
>
> it's good to see more Skein stuff. it's a great crypto hash and one of the
> few remaining candidate for SHA-3.
>
> Have you seen the cryptohash package
> http://hackage.haskell.org/package/cryptohash ?
>
> I always wanted to expose more skein operations specially the hmac function,
> but never came around to, and maybe it would be good to merge to avoid
> duplicating efforts ?

I'm aware of cryptohash.  I just went through the lazy route of
binding to the C library instead of implementing those UBI details =).
 It would be nice to merge and have everything on cryptohash though.
And I guess that cryptohash may become faster than skein because the C
library has some implementation details that are unneeded (e.g. it has
a buffer, but hash/hash' are kind enough to only give full buffers to
the libraries).

Also, it seems that cryptohash's Skein is currently broken.  The skein
package comes with the "golden" KATs sent by the Skein team to the
NIST, and passes everything.  OTOH, cryptohash's Skein256/Skein512 do
not agree with skein's Skein_256_256/Skein_512_512.  I've attached a
test suite that quickchecks if both implementations give the same
answer.  My hunch is that you are using the wrong constants, because
the first test case (the empty string) already fails:

1) cryptohash and skein have the same implementation of Skein-256-256 FAILED
*** Failed!
skein:      bc 27 63 f7 07 e2 62 b8 0e 03 13 79 15 43 a7 ab 0a 4b 6c
d0 83 27 0a fb 2f ce 42 72 e1 bb 0a a9
cryptohash: 0b 04 10 3b 82 8c dd ae bc f5 92 ac 84 5e ca fd 58 87 f6
12 30 a7 55 40 6d 38 d8 53 76 e1 ae 08
 (after 1 test):
(none)

2) cryptohash and skein have the same implementation of Skein-512-512 FAILED
*** Failed!
skein:      d3 f7 26 3a 09 83 7f 4c e5 c8 ef 70 a5 dd ff ac 7b 92 d6
c2 ac e5 a1 22 65 bd 5b 59 32 60 a3 ff 20 d8 b4 b4 c5 49 4e 94 54 48
b3 7a bb 1f c5 26 f6 b4 60 89 20 8f de 93 8d 7f 23 72 4c 4b df b7
cryptohash: 5a f6 8a 49 12 e0 a6 18 7a 00 49 47 a9 d2 a3 7d 7a 1f 08
73 f0 bd d9 dc 64 83 8e ce 60 da 55 35 c2 a5 5d 03 9b d5 8e 17 89 48
99 6b 7a 83 36 48 6e d9 69 c8 94 be 65 8e 47 d5 95 a5 a9 b8 6a 8b
 (after 1 test):
(none)

Cheers, =D

-- 
Felipe.
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
import Data.Char (intToDigit)
import Data.List (intersperse)
import Test.Hspec.Monadic hiding (Result)
import Test.QuickCheck hiding (Result(..), reason, property)
import Test.QuickCheck.Property (succeeded, failed, Result(..))
import Test.Hspec.QuickCheck

import qualified Data.ByteString as B
import Data.Serialize (encode)

import Crypto.Classes (Hash, hash')
import Crypto.Hash.Skein256 (Skein256)
import Crypto.Hash.Skein512 (Skein512)
import Crypto.Skein (Skein_256_256, Skein_512_512)

main :: IO ()
main = hspecX $ do
         describe "cryptohash and skein have the same implementation of" $ do
           it "Skein-256-256" $ property $ same (u :: Skein_256_256) (u :: Skein256)
           it "Skein-512-512" $ property $ same (u :: Skein_512_512) (u :: Skein512)

u :: a
u = undefined

same :: (Hash ctx1 dig1, Hash ctx2 dig2) => dig1 -> dig2 -> Input -> Result
same dig1 dig2 (Input inp) =
    let h1 = hash' inp `asTypeOf` dig1
        h2 = hash' inp `asTypeOf` dig2
    in if encode h1 == encode h2
       then succeeded
       else failed { reason = "\nskein:      " ++ show (Input $ encode h1) ++
                              "\ncryptohash: " ++ show (Input $ encode h2) ++ "\n"}


newtype Input = Input B.ByteString

instance Show Input where
    show (Input bs)
        | B.null bs = "(none)"
        | otherwise = concat $ intersperse " " $ map toHex $ B.unpack bs
        where toHex = map intToDigit . (\(a,b) -> [a,b]) . (`divMod` 16) . fromIntegral

instance Arbitrary Input where
    arbitrary = (Input . B.pack) `fmap` arbitrary
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to