File: Types.hs

package info (click to toggle)
haskell-cryptohash 0.11.9-11
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 336 kB
  • sloc: haskell: 1,325; ansic: 991; makefile: 4
file content (48 lines) | stat: -rw-r--r-- 1,328 bytes parent folder | download | duplicates (5)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
{-# LANGUAGE PackageImports #-}
-- |
-- Module      : Crypto.Hash.Types
-- License     : BSD-style
-- Maintainer  : Vincent Hanquez <vincent@snarc.org>
-- Stability   : experimental
-- Portability : unknown
--
-- Crypto hash types definitions
--
module Crypto.Hash.Types
    ( Context(..)
    , Digest(..)
    -- * deprecated
    , contextToByteString
    , digestToByteString
    )
    where

import Data.ByteString (ByteString)
import Data.Byteable
import qualified Data.ByteArray as B (convert)
import qualified "cryptonite" Crypto.Hash as H

-- | Represent a context for a given hash algorithm.
newtype Context a = Context (H.Context a)

instance Byteable (Context a) where
    toBytes (Context ctx) = B.convert ctx

--- | return the binary bytestring. deprecated use toBytes.
contextToByteString :: Context a -> ByteString
contextToByteString = toBytes

-- | Represent a digest for a given hash algorithm.
newtype Digest a = Digest (H.Digest a)
    deriving (Eq,Ord)

instance Byteable (Digest a) where
    toBytes (Digest dig) = B.convert dig

-- | return the binary bytestring. deprecated use toBytes.
{-# DEPRECATED digestToByteString "use toBytes from byteable:Data.Byteable" #-}
digestToByteString :: Digest a -> ByteString
digestToByteString = toBytes

instance Show (Digest a) where
    show (Digest dig) = show dig