summaryrefslogtreecommitdiff
path: root/dht/src/Crypto/Nonce.hs
blob: 263f9b0a99530b9d539c3c31a3c6712173137f08 (plain)
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
49
{-# LANGUAGE DeriveDataTypeable         #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Crypto.Nonce
    ( Nonce32
    , generateNonce32
    , zeros32
    ) where

import Crypto.Random
import Data.ByteArray                   as BA
import Data.ByteString                  as B
import qualified Data.ByteString.Base64 as Base64
import Data.ByteString.Char8            as B8
import Data.Data
import Data.Serialize
import Data.Sized

newtype Nonce32 = Nonce32 ByteString
 deriving (Eq, Ord, ByteArrayAccess, Data)

bin2base64 :: ByteArrayAccess bs => bs -> String
bin2base64 = B8.unpack . Base64.encode . BA.convert

instance Show Nonce32 where
    showsPrec d nonce = mappend $ bin2base64 nonce

instance Read Nonce32 where
    readsPrec _ str = either (const []) id $ do
        let (ds,ss) = Prelude.splitAt 43 str
        ss' <- case ss of
                '=':xs -> Right xs -- optional terminating '='
                _      -> Right ss
        bs <- Base64.decode (B8.pack $ ds ++ ['='])
        if B.length bs == 32
            then Right [ (Nonce32 bs, ss') ]
            else Left  "Truncated Nonce32 (expected 43 base64 digits)."

instance Serialize Nonce32 where
    get = Nonce32 <$> getBytes 32
    put (Nonce32 bs) = putByteString bs

instance Sized Nonce32 where size = ConstSize 32


zeros32 :: Nonce32
zeros32 = Nonce32 $ BA.replicate 32 0

generateNonce32 :: MonadRandom m => m Nonce32
generateNonce32 = Nonce32 <$> getRandomBytes 32