1-- |
2-- Module      : Crypto.Hash.IO
3-- License     : BSD-style
4-- Maintainer  : Vincent Hanquez <vincent@snarc.org>
5-- Stability   : experimental
6-- Portability : unknown
7--
8-- Generalized impure cryptographic hash interface
9--
10{-# LANGUAGE GeneralizedNewtypeDeriving #-}
11{-# LANGUAGE ScopedTypeVariables        #-}
12module Crypto.Hash.IO
13    ( HashAlgorithm(..)
14    , MutableContext
15    , hashMutableInit
16    , hashMutableInitWith
17    , hashMutableUpdate
18    , hashMutableFinalize
19    , hashMutableReset
20    ) where
21
22import           Crypto.Hash.Types
23import qualified Crypto.Internal.ByteArray as B
24import           Foreign.Ptr
25
26-- | A Mutable hash context
27newtype MutableContext a = MutableContext B.Bytes
28    deriving (B.ByteArrayAccess)
29
30-- | Create a new mutable hash context.
31--
32-- the algorithm used is automatically determined from the return constraint.
33hashMutableInit :: HashAlgorithm alg => IO (MutableContext alg)
34hashMutableInit = doInit undefined B.alloc
35  where
36        doInit :: HashAlgorithm a => a -> (Int -> (Ptr (Context a) -> IO ()) -> IO B.Bytes) -> IO (MutableContext a)
37        doInit alg alloc = MutableContext `fmap` alloc (hashInternalContextSize alg) hashInternalInit
38
39-- | Create a new mutable hash context.
40--
41-- The algorithm is explicitely passed as parameter
42hashMutableInitWith :: HashAlgorithm alg => alg -> IO (MutableContext alg)
43hashMutableInitWith _ = hashMutableInit
44
45-- | Update a mutable hash context in place
46hashMutableUpdate :: (B.ByteArrayAccess ba, HashAlgorithm a) => MutableContext a -> ba -> IO ()
47hashMutableUpdate mc dat = doUpdate mc (B.withByteArray mc)
48  where doUpdate :: HashAlgorithm a => MutableContext a -> ((Ptr (Context a) -> IO ()) -> IO ()) -> IO ()
49        doUpdate _ withCtx =
50            withCtx             $ \ctx ->
51            B.withByteArray dat $ \d   ->
52                hashInternalUpdate ctx d (fromIntegral $ B.length dat)
53
54-- | Finalize a mutable hash context and compute a digest
55hashMutableFinalize :: forall a . HashAlgorithm a => MutableContext a -> IO (Digest a)
56hashMutableFinalize mc = do
57    b <- B.alloc (hashDigestSize (undefined :: a)) $ \dig -> B.withByteArray mc $ \(ctx :: Ptr (Context a)) -> hashInternalFinalize ctx dig
58    return $ Digest b
59
60-- | Reset the mutable context to the initial state of the hash
61hashMutableReset :: HashAlgorithm a => MutableContext a -> IO ()
62hashMutableReset mc = doReset mc (B.withByteArray mc)
63  where
64    doReset :: HashAlgorithm a => MutableContext a -> ((Ptr (Context a) -> IO ()) -> IO ()) -> IO ()
65    doReset _ withCtx = withCtx hashInternalInit
66