Skip to content
This repository has been archived by the owner on Sep 20, 2023. It is now read-only.

Commit

Permalink
Merge pull request #133 from haskell-crypto/typeable
Browse files Browse the repository at this point in the history
add Typeable for all hash algorithms
  • Loading branch information
vincenthz committed Feb 14, 2017
2 parents e3ef068 + 7c33fce commit 550a689
Show file tree
Hide file tree
Showing 22 changed files with 79 additions and 35 deletions.
4 changes: 3 additions & 1 deletion Crypto/Hash/Blake2b.hs
Expand Up @@ -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
Expand Down
4 changes: 3 additions & 1 deletion Crypto/Hash/Blake2bp.hs
Expand Up @@ -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
Expand Down
6 changes: 4 additions & 2 deletions Crypto/Hash/Blake2s.hs
Expand Up @@ -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
Expand All @@ -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
Expand Down
6 changes: 4 additions & 2 deletions Crypto/Hash/Blake2sp.hs
Expand Up @@ -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
Expand All @@ -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
Expand Down
10 changes: 6 additions & 4 deletions Crypto/Hash/Keccak.hs
Expand Up @@ -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
Expand All @@ -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
Expand All @@ -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
Expand All @@ -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
Expand Down
4 changes: 3 additions & 1 deletion Crypto/Hash/MD2.hs
Expand Up @@ -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
Expand Down
4 changes: 3 additions & 1 deletion Crypto/Hash/MD4.hs
Expand Up @@ -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
Expand Down
4 changes: 3 additions & 1 deletion Crypto/Hash/MD5.hs
Expand Up @@ -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
Expand Down
4 changes: 3 additions & 1 deletion Crypto/Hash/RIPEMD160.hs
Expand Up @@ -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
Expand Down
4 changes: 3 additions & 1 deletion Crypto/Hash/SHA1.hs
Expand Up @@ -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
Expand Down
4 changes: 3 additions & 1 deletion Crypto/Hash/SHA224.hs
Expand Up @@ -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
Expand Down
4 changes: 3 additions & 1 deletion Crypto/Hash/SHA256.hs
Expand Up @@ -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
Expand Down
10 changes: 6 additions & 4 deletions Crypto/Hash/SHA3.hs
Expand Up @@ -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
Expand All @@ -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
Expand All @@ -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
Expand All @@ -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
Expand Down
4 changes: 3 additions & 1 deletion Crypto/Hash/SHA384.hs
Expand Up @@ -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
Expand Down
4 changes: 3 additions & 1 deletion Crypto/Hash/SHA512.hs
Expand Up @@ -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
Expand Down

0 comments on commit 550a689

Please sign in to comment.