add Typeable to hash algorithm
This commit is contained in:
parent
9227ab9225
commit
7c33fcedb4
@ -9,18 +9,20 @@
|
||||
-- Blake2b cryptographic hash.
|
||||
--
|
||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
module Crypto.Hash.Blake2b
|
||||
( Blake2b_512 (..)
|
||||
) where
|
||||
|
||||
import Crypto.Hash.Types
|
||||
import Foreign.Ptr (Ptr)
|
||||
import Data.Typeable
|
||||
import Data.Word (Word8, Word32)
|
||||
|
||||
|
||||
-- | Blake2b (512 bits) cryptographic hash algorithm
|
||||
data Blake2b_512 = Blake2b_512
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm Blake2b_512 where
|
||||
hashBlockSize _ = 128
|
||||
|
||||
@ -9,18 +9,20 @@
|
||||
-- Blake2bp cryptographic hash.
|
||||
--
|
||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
module Crypto.Hash.Blake2bp
|
||||
( Blake2bp_512 (..)
|
||||
) where
|
||||
|
||||
import Crypto.Hash.Types
|
||||
import Foreign.Ptr (Ptr)
|
||||
import Data.Typeable
|
||||
import Data.Word (Word8, Word32)
|
||||
|
||||
|
||||
-- | Blake2bp (512 bits) cryptographic hash algorithm
|
||||
data Blake2bp_512 = Blake2bp_512
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm Blake2bp_512 where
|
||||
hashBlockSize _ = 128
|
||||
|
||||
@ -9,18 +9,20 @@
|
||||
-- Blake2s cryptographic hash.
|
||||
--
|
||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
module Crypto.Hash.Blake2s
|
||||
( Blake2s_224 (..), Blake2s_256 (..)
|
||||
) where
|
||||
|
||||
import Crypto.Hash.Types
|
||||
import Foreign.Ptr (Ptr)
|
||||
import Data.Typeable
|
||||
import Data.Word (Word8, Word32)
|
||||
|
||||
|
||||
-- | Blake2s (224 bits) cryptographic hash algorithm
|
||||
data Blake2s_224 = Blake2s_224
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm Blake2s_224 where
|
||||
hashBlockSize _ = 64
|
||||
@ -32,7 +34,7 @@ instance HashAlgorithm Blake2s_224 where
|
||||
|
||||
-- | Blake2s (256 bits) cryptographic hash algorithm
|
||||
data Blake2s_256 = Blake2s_256
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm Blake2s_256 where
|
||||
hashBlockSize _ = 64
|
||||
|
||||
@ -9,18 +9,20 @@
|
||||
-- Blake2sp cryptographic hash.
|
||||
--
|
||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
module Crypto.Hash.Blake2sp
|
||||
( Blake2sp_224 (..), Blake2sp_256 (..)
|
||||
) where
|
||||
|
||||
import Crypto.Hash.Types
|
||||
import Foreign.Ptr (Ptr)
|
||||
import Data.Typeable
|
||||
import Data.Word (Word8, Word32)
|
||||
|
||||
|
||||
-- | Blake2sp (224 bits) cryptographic hash algorithm
|
||||
data Blake2sp_224 = Blake2sp_224
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm Blake2sp_224 where
|
||||
hashBlockSize _ = 64
|
||||
@ -32,7 +34,7 @@ instance HashAlgorithm Blake2sp_224 where
|
||||
|
||||
-- | Blake2sp (256 bits) cryptographic hash algorithm
|
||||
data Blake2sp_256 = Blake2sp_256
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm Blake2sp_256 where
|
||||
hashBlockSize _ = 64
|
||||
|
||||
@ -9,18 +9,20 @@
|
||||
-- Keccak cryptographic hash.
|
||||
--
|
||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
module Crypto.Hash.Keccak
|
||||
( Keccak_224 (..), Keccak_256 (..), Keccak_384 (..), Keccak_512 (..)
|
||||
) where
|
||||
|
||||
import Crypto.Hash.Types
|
||||
import Foreign.Ptr (Ptr)
|
||||
import Data.Typeable
|
||||
import Data.Word (Word8, Word32)
|
||||
|
||||
|
||||
-- | Keccak (224 bits) cryptographic hash algorithm
|
||||
data Keccak_224 = Keccak_224
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm Keccak_224 where
|
||||
hashBlockSize _ = 144
|
||||
@ -32,7 +34,7 @@ instance HashAlgorithm Keccak_224 where
|
||||
|
||||
-- | Keccak (256 bits) cryptographic hash algorithm
|
||||
data Keccak_256 = Keccak_256
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm Keccak_256 where
|
||||
hashBlockSize _ = 136
|
||||
@ -44,7 +46,7 @@ instance HashAlgorithm Keccak_256 where
|
||||
|
||||
-- | Keccak (384 bits) cryptographic hash algorithm
|
||||
data Keccak_384 = Keccak_384
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm Keccak_384 where
|
||||
hashBlockSize _ = 104
|
||||
@ -56,7 +58,7 @@ instance HashAlgorithm Keccak_384 where
|
||||
|
||||
-- | Keccak (512 bits) cryptographic hash algorithm
|
||||
data Keccak_512 = Keccak_512
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm Keccak_512 where
|
||||
hashBlockSize _ = 72
|
||||
|
||||
@ -9,15 +9,17 @@
|
||||
-- MD2 cryptographic hash.
|
||||
--
|
||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
module Crypto.Hash.MD2 ( MD2 (..) ) where
|
||||
|
||||
import Crypto.Hash.Types
|
||||
import Foreign.Ptr (Ptr)
|
||||
import Data.Typeable
|
||||
import Data.Word (Word8, Word32)
|
||||
|
||||
-- | MD2 cryptographic hash algorithm
|
||||
data MD2 = MD2
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm MD2 where
|
||||
hashBlockSize _ = 16
|
||||
|
||||
@ -9,15 +9,17 @@
|
||||
-- MD4 cryptographic hash.
|
||||
--
|
||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
module Crypto.Hash.MD4 ( MD4 (..) ) where
|
||||
|
||||
import Crypto.Hash.Types
|
||||
import Foreign.Ptr (Ptr)
|
||||
import Data.Typeable
|
||||
import Data.Word (Word8, Word32)
|
||||
|
||||
-- | MD4 cryptographic hash algorithm
|
||||
data MD4 = MD4
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm MD4 where
|
||||
hashBlockSize _ = 64
|
||||
|
||||
@ -9,15 +9,17 @@
|
||||
-- MD5 cryptographic hash.
|
||||
--
|
||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
module Crypto.Hash.MD5 ( MD5 (..) ) where
|
||||
|
||||
import Crypto.Hash.Types
|
||||
import Foreign.Ptr (Ptr)
|
||||
import Data.Typeable
|
||||
import Data.Word (Word8, Word32)
|
||||
|
||||
-- | MD5 cryptographic hash algorithm
|
||||
data MD5 = MD5
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm MD5 where
|
||||
hashBlockSize _ = 64
|
||||
|
||||
@ -9,15 +9,17 @@
|
||||
-- RIPEMD160 cryptographic hash.
|
||||
--
|
||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
module Crypto.Hash.RIPEMD160 ( RIPEMD160 (..) ) where
|
||||
|
||||
import Crypto.Hash.Types
|
||||
import Foreign.Ptr (Ptr)
|
||||
import Data.Typeable
|
||||
import Data.Word (Word8, Word32)
|
||||
|
||||
-- | RIPEMD160 cryptographic hash algorithm
|
||||
data RIPEMD160 = RIPEMD160
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm RIPEMD160 where
|
||||
hashBlockSize _ = 64
|
||||
|
||||
@ -9,15 +9,17 @@
|
||||
-- SHA1 cryptographic hash.
|
||||
--
|
||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
module Crypto.Hash.SHA1 ( SHA1 (..) ) where
|
||||
|
||||
import Crypto.Hash.Types
|
||||
import Foreign.Ptr (Ptr)
|
||||
import Data.Typeable
|
||||
import Data.Word (Word8, Word32)
|
||||
|
||||
-- | SHA1 cryptographic hash algorithm
|
||||
data SHA1 = SHA1
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm SHA1 where
|
||||
hashBlockSize _ = 64
|
||||
|
||||
@ -9,15 +9,17 @@
|
||||
-- SHA224 cryptographic hash.
|
||||
--
|
||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
module Crypto.Hash.SHA224 ( SHA224 (..) ) where
|
||||
|
||||
import Crypto.Hash.Types
|
||||
import Foreign.Ptr (Ptr)
|
||||
import Data.Typeable
|
||||
import Data.Word (Word8, Word32)
|
||||
|
||||
-- | SHA224 cryptographic hash algorithm
|
||||
data SHA224 = SHA224
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm SHA224 where
|
||||
hashBlockSize _ = 64
|
||||
|
||||
@ -9,15 +9,17 @@
|
||||
-- SHA256 cryptographic hash.
|
||||
--
|
||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
module Crypto.Hash.SHA256 ( SHA256 (..) ) where
|
||||
|
||||
import Crypto.Hash.Types
|
||||
import Foreign.Ptr (Ptr)
|
||||
import Data.Typeable
|
||||
import Data.Word (Word8, Word32)
|
||||
|
||||
-- | SHA256 cryptographic hash algorithm
|
||||
data SHA256 = SHA256
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm SHA256 where
|
||||
hashBlockSize _ = 64
|
||||
|
||||
@ -9,18 +9,20 @@
|
||||
-- SHA3 cryptographic hash.
|
||||
--
|
||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
module Crypto.Hash.SHA3
|
||||
( SHA3_224 (..), SHA3_256 (..), SHA3_384 (..), SHA3_512 (..)
|
||||
) where
|
||||
|
||||
import Crypto.Hash.Types
|
||||
import Foreign.Ptr (Ptr)
|
||||
import Data.Typeable
|
||||
import Data.Word (Word8, Word32)
|
||||
|
||||
|
||||
-- | SHA3 (224 bits) cryptographic hash algorithm
|
||||
data SHA3_224 = SHA3_224
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm SHA3_224 where
|
||||
hashBlockSize _ = 144
|
||||
@ -32,7 +34,7 @@ instance HashAlgorithm SHA3_224 where
|
||||
|
||||
-- | SHA3 (256 bits) cryptographic hash algorithm
|
||||
data SHA3_256 = SHA3_256
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm SHA3_256 where
|
||||
hashBlockSize _ = 136
|
||||
@ -44,7 +46,7 @@ instance HashAlgorithm SHA3_256 where
|
||||
|
||||
-- | SHA3 (384 bits) cryptographic hash algorithm
|
||||
data SHA3_384 = SHA3_384
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm SHA3_384 where
|
||||
hashBlockSize _ = 104
|
||||
@ -56,7 +58,7 @@ instance HashAlgorithm SHA3_384 where
|
||||
|
||||
-- | SHA3 (512 bits) cryptographic hash algorithm
|
||||
data SHA3_512 = SHA3_512
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm SHA3_512 where
|
||||
hashBlockSize _ = 72
|
||||
|
||||
@ -9,15 +9,17 @@
|
||||
-- SHA384 cryptographic hash.
|
||||
--
|
||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
module Crypto.Hash.SHA384 ( SHA384 (..) ) where
|
||||
|
||||
import Crypto.Hash.Types
|
||||
import Foreign.Ptr (Ptr)
|
||||
import Data.Typeable
|
||||
import Data.Word (Word8, Word32)
|
||||
|
||||
-- | SHA384 cryptographic hash algorithm
|
||||
data SHA384 = SHA384
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm SHA384 where
|
||||
hashBlockSize _ = 128
|
||||
|
||||
@ -9,15 +9,17 @@
|
||||
-- SHA512 cryptographic hash.
|
||||
--
|
||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
module Crypto.Hash.SHA512 ( SHA512 (..) ) where
|
||||
|
||||
import Crypto.Hash.Types
|
||||
import Foreign.Ptr (Ptr)
|
||||
import Data.Typeable
|
||||
import Data.Word (Word8, Word32)
|
||||
|
||||
-- | SHA512 cryptographic hash algorithm
|
||||
data SHA512 = SHA512
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm SHA512 where
|
||||
hashBlockSize _ = 128
|
||||
|
||||
@ -9,18 +9,20 @@
|
||||
-- SHA512t cryptographic hash.
|
||||
--
|
||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
module Crypto.Hash.SHA512t
|
||||
( SHA512t_224 (..), SHA512t_256 (..)
|
||||
) where
|
||||
|
||||
import Crypto.Hash.Types
|
||||
import Foreign.Ptr (Ptr)
|
||||
import Data.Typeable
|
||||
import Data.Word (Word8, Word32)
|
||||
|
||||
|
||||
-- | SHA512t (224 bits) cryptographic hash algorithm
|
||||
data SHA512t_224 = SHA512t_224
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm SHA512t_224 where
|
||||
hashBlockSize _ = 128
|
||||
@ -32,7 +34,7 @@ instance HashAlgorithm SHA512t_224 where
|
||||
|
||||
-- | SHA512t (256 bits) cryptographic hash algorithm
|
||||
data SHA512t_256 = SHA512t_256
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm SHA512t_256 where
|
||||
hashBlockSize _ = 128
|
||||
|
||||
@ -9,18 +9,20 @@
|
||||
-- Skein256 cryptographic hash.
|
||||
--
|
||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
module Crypto.Hash.Skein256
|
||||
( Skein256_224 (..), Skein256_256 (..)
|
||||
) where
|
||||
|
||||
import Crypto.Hash.Types
|
||||
import Foreign.Ptr (Ptr)
|
||||
import Data.Typeable
|
||||
import Data.Word (Word8, Word32)
|
||||
|
||||
|
||||
-- | Skein256 (224 bits) cryptographic hash algorithm
|
||||
data Skein256_224 = Skein256_224
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm Skein256_224 where
|
||||
hashBlockSize _ = 32
|
||||
@ -32,7 +34,7 @@ instance HashAlgorithm Skein256_224 where
|
||||
|
||||
-- | Skein256 (256 bits) cryptographic hash algorithm
|
||||
data Skein256_256 = Skein256_256
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm Skein256_256 where
|
||||
hashBlockSize _ = 32
|
||||
|
||||
@ -9,18 +9,20 @@
|
||||
-- Skein512 cryptographic hash.
|
||||
--
|
||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
module Crypto.Hash.Skein512
|
||||
( Skein512_224 (..), Skein512_256 (..), Skein512_384 (..), Skein512_512 (..)
|
||||
) where
|
||||
|
||||
import Crypto.Hash.Types
|
||||
import Foreign.Ptr (Ptr)
|
||||
import Data.Typeable
|
||||
import Data.Word (Word8, Word32)
|
||||
|
||||
|
||||
-- | Skein512 (224 bits) cryptographic hash algorithm
|
||||
data Skein512_224 = Skein512_224
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm Skein512_224 where
|
||||
hashBlockSize _ = 64
|
||||
@ -32,7 +34,7 @@ instance HashAlgorithm Skein512_224 where
|
||||
|
||||
-- | Skein512 (256 bits) cryptographic hash algorithm
|
||||
data Skein512_256 = Skein512_256
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm Skein512_256 where
|
||||
hashBlockSize _ = 64
|
||||
@ -44,7 +46,7 @@ instance HashAlgorithm Skein512_256 where
|
||||
|
||||
-- | Skein512 (384 bits) cryptographic hash algorithm
|
||||
data Skein512_384 = Skein512_384
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm Skein512_384 where
|
||||
hashBlockSize _ = 64
|
||||
@ -56,7 +58,7 @@ instance HashAlgorithm Skein512_384 where
|
||||
|
||||
-- | Skein512 (512 bits) cryptographic hash algorithm
|
||||
data Skein512_512 = Skein512_512
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm Skein512_512 where
|
||||
hashBlockSize _ = 64
|
||||
|
||||
@ -9,15 +9,17 @@
|
||||
-- Tiger cryptographic hash.
|
||||
--
|
||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
module Crypto.Hash.Tiger ( Tiger (..) ) where
|
||||
|
||||
import Crypto.Hash.Types
|
||||
import Foreign.Ptr (Ptr)
|
||||
import Data.Typeable
|
||||
import Data.Word (Word8, Word32)
|
||||
|
||||
-- | Tiger cryptographic hash algorithm
|
||||
data Tiger = Tiger
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm Tiger where
|
||||
hashBlockSize _ = 64
|
||||
|
||||
@ -9,15 +9,17 @@
|
||||
-- Whirlpool cryptographic hash.
|
||||
--
|
||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
module Crypto.Hash.Whirlpool ( Whirlpool (..) ) where
|
||||
|
||||
import Crypto.Hash.Types
|
||||
import Foreign.Ptr (Ptr)
|
||||
import Data.Typeable
|
||||
import Data.Word (Word8, Word32)
|
||||
|
||||
-- | Whirlpool cryptographic hash algorithm
|
||||
data Whirlpool = Whirlpool
|
||||
deriving (Show)
|
||||
deriving (Show,Typeable)
|
||||
|
||||
instance HashAlgorithm Whirlpool where
|
||||
hashBlockSize _ = 64
|
||||
|
||||
Loading…
Reference in New Issue
Block a user