module Raaz.Hash.Internal.HMAC
( HMAC (..)
, hmac, hmacFile, hmacSource
, hmac', hmacFile', hmacSource'
) where
import Control.Applicative
import Control.Monad.IO.Class (liftIO)
import Data.Bits (xor)
import Data.ByteString.Char8 (ByteString)
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as L
import Data.Monoid
import Data.String
import Foreign.Ptr ( castPtr )
import Foreign.Storable ( Storable(..) )
import Prelude hiding (length, replicate)
import System.IO
import System.IO.Unsafe (unsafePerformIO)
import Raaz.Core
import Raaz.Core.Parse.Applicative
import Raaz.Core.Write
import Raaz.Hash.Internal
newtype HMACKey h = HMACKey { unKey :: B.ByteString } deriving Monoid
instance (Hash h, Recommendation h) => Storable (HMACKey h) where
sizeOf _ = fromIntegral $ blockSize (undefined :: h)
alignment _ = alignment (undefined :: Align)
peek = unsafeRunParser (HMACKey <$> parseByteString (blockSize (undefined :: h))) . castPtr
poke ptr key = unsafeWrite (writeByteString $ hmacAdjustKey key) $ castPtr ptr
hmacAdjustKey :: (Hash h, Recommendation h, Encodable h)
=> HMACKey h
-> ByteString
hmacAdjustKey key = padIt trimedKey
where keyStr = unKey key
trimedKey = if length keyStr > sz
then toByteString
$ hash keyStr `asTypeOf` theHash key
else keyStr
padIt k = k <> replicate (sz length k) 0
sz = blockSize $ theHash key
theHash :: HMACKey h -> h
theHash _ = undefined
instance (Hash h, Recommendation h, Encodable h) => EndianStore (HMACKey h) where
store = poke . castPtr
load = peek . castPtr
instance (Hash h, Recommendation h, Encodable h) => Random (HMACKey h)
instance (Hash h, Recommendation h, Encodable h) => Encodable (HMACKey h)
instance IsString (HMACKey h) where
fromString = HMACKey
. (decodeFormat :: Base16 -> ByteString)
. fromString
instance Show (HMACKey h) where
show = show . (encodeByteString :: ByteString -> Base16) . unKey
newtype HMAC h = HMAC {unHMAC :: h} deriving ( Eq, Storable
, EndianStore
, Encodable
, IsString
)
instance Show h => Show (HMAC h) where
show = show . unHMAC
instance (Hash h) => Primitive (HMAC h) where
blockSize _ = blockSize (undefined :: h)
type Implementation (HMAC h) = Implementation h
instance (Hash h, Recommendation h) => Recommendation (HMAC h) where
recommended _ = recommended (undefined :: h)
instance Hash h => Symmetric (HMAC h) where
type Key (HMAC h) = HMACKey h
hmac :: ( Hash h, Recommendation h, PureByteSource src )
=> Key (HMAC h)
-> src
-> HMAC h
hmac key = unsafePerformIO . hmacSource key
hmacFile :: (Hash h, Recommendation h)
=> Key (HMAC h)
-> FilePath
-> IO (HMAC h)
hmacFile key fileName = withBinaryFile fileName ReadMode $ hmacSource key
hmacSource :: ( Hash h, Recommendation h, ByteSource src )
=> Key (HMAC h)
-> src
-> IO (HMAC h)
hmacSource = go undefined
where go :: (Hash h, Recommendation h, ByteSource src)
=> h -> Key (HMAC h) -> src -> IO (HMAC h)
go h = hmacSource' (recommended h)
hmac' :: ( Hash h, Recommendation h, PureByteSource src )
=> Implementation h
-> Key (HMAC h)
-> src
-> HMAC h
hmac' impl key = unsafePerformIO . hmacSource' impl key
hmacFile' :: (Hash h, Recommendation h)
=> Implementation h
-> Key (HMAC h)
-> FilePath
-> IO (HMAC h)
hmacFile' impl key fileName = withBinaryFile fileName ReadMode $ hmacSource' impl key
hmacSource' :: (Hash h, Recommendation h, ByteSource src)
=> Implementation h
-> Key (HMAC h)
-> src
-> IO (HMAC h)
hmacSource' (SomeHashI hI) key src =
insecurely $ do
initialise ()
allocate bufSize $ \ ptr -> do
liftIO $ unsafeCopyToPointer innerFirstBlock ptr
compress hI ptr 1
innerHash <- completeHashing hI src
initialise ()
allocate bufSize $ \ ptr -> do
liftIO $ unsafeCopyToPointer outerFirstBlock ptr
compress hI ptr 1
HMAC <$> completeHashing hI (toByteString innerHash)
where innerFirstBlock = B.map (xor 0x36) $ hmacAdjustKey key
outerFirstBlock = B.map (xor 0x5c) $ hmacAdjustKey key
bufSize = length innerFirstBlock