diff --git a/Crypto/MAC/Poly1305.hs b/Crypto/MAC/Poly1305.hs new file mode 100644 index 0000000..93410fb --- /dev/null +++ b/Crypto/MAC/Poly1305.hs @@ -0,0 +1,97 @@ +{-# LANGUAGE ForeignFunctionInterface #-} + +-- | +-- Module : Crypto.MAC.Poly1305 +-- License : BSD-style +-- Maintainer : Vincent Hanquez +-- Stability : experimental +-- Portability : unknown +-- +-- Poly1305 implementation +-- +module Crypto.MAC.Poly1305 + ( Ctx + , Auth + + -- * Incremental MAC Functions + , initialize -- :: Ctx + , update -- :: Ctx -> ByteString -> Ctx + , updates -- :: Ctx -> [ByteString] -> Ctx + , finalize -- :: Ctx -> Auth + -- * One-pass MAC function + , auth + ) where + +import Prelude hiding (init) +import Foreign.Ptr +import Foreign.C.Types +import qualified Data.ByteString as B +import qualified Data.ByteString.Internal as B +import Data.ByteString (ByteString) +import Data.Word +import Data.Byteable +import System.IO.Unsafe +import Data.SecureMem + +-- | Poly1305 Context +newtype Ctx = Ctx SecureMem + +-- | Poly1305 Auth +newtype Auth = Auth ByteString + +instance Byteable Auth where + toBytes (Auth b) = b + +foreign import ccall unsafe "cryptonite_poly1305.h cryptonite_poly1305_init" + c_poly1305_init :: Ptr Ctx -> Ptr Word8 -> IO () + +foreign import ccall "cryptonite_poly1305.h cryptonite_poly1305_update" + c_poly1305_update :: Ptr Ctx -> Ptr Word8 -> CUInt -> IO () + +foreign import ccall unsafe "cryptonite_poly1305.h cryptonite_poly1305_finalize" + c_poly1305_finalize :: Ptr Word8 -> Ptr Ctx -> IO () + +-- | initialize a Poly1305 context +initialize :: Byteable key + => key + -> Ctx +initialize key + | byteableLength key /= 32 = error "Poly1305: key length expected 32 bytes" + | otherwise = Ctx $ unsafePerformIO $ do + withBytePtr key $ \keyPtr -> + createSecureMem 64 {- FIXME -} $ \ctxPtr -> + c_poly1305_init (castPtr ctxPtr) keyPtr +{-# NOINLINE initialize #-} + +-- | update a context with a bytestring +update :: Ctx -> ByteString -> Ctx +update (Ctx prevCtx) d = unsafePerformIO $ do + ctx <- secureMemCopy prevCtx + withSecureMemPtr ctx $ \ctxPtr -> + withBytePtr d $ \dataPtr -> + c_poly1305_update (castPtr ctxPtr) dataPtr (fromIntegral $ B.length d) + return $ Ctx ctx +{-# NOINLINE update #-} + +-- | updates a context with multiples bytestring +updates :: Ctx -> [ByteString] -> Ctx +updates (Ctx prevCtx) d = unsafePerformIO $ do + ctx <- secureMemCopy prevCtx + withSecureMemPtr ctx (loop d . castPtr) + return $ Ctx ctx + where loop [] _ = return () + loop (x:xs) ctxPtr = do + withBytePtr x $ \dataPtr -> c_poly1305_update ctxPtr dataPtr (fromIntegral $ B.length x) + loop xs ctxPtr +{-# NOINLINE updates #-} + +-- | finalize the context into a digest bytestring +finalize :: Ctx -> Auth +finalize (Ctx prevCtx) = Auth $ B.unsafeCreate 16 $ \dst -> do + ctx <- secureMemCopy prevCtx + withSecureMemPtr ctx $ \ctxPtr -> c_poly1305_finalize dst (castPtr ctxPtr) +{-# NOINLINE finalize #-} + +-- | Auth +auth :: Byteable key => key -> ByteString -> Auth +auth key = finalize . update (initialize key) diff --git a/cryptonite.cabal b/cryptonite.cabal index bad6975..6698a03 100644 --- a/cryptonite.cabal +++ b/cryptonite.cabal @@ -21,6 +21,7 @@ source-repository head Library Exposed-modules: Crypto.Cipher.ChaCha + Other-modules: Crypto.MAC.Poly1305 Build-depends: base >= 4 && < 5 , bytestring , securemem @@ -28,6 +29,7 @@ Library ghc-options: -Wall -fwarn-tabs -optc-O3 default-language: Haskell2010 C-sources: cbits/cryptonite_chacha.c + , cbits/cryptonite_poly1305.c if (arch(i386) || arch(x86_64)) CPP-options: -DARCH_IS_LITTLE_ENDIAN