summaryrefslogtreecommitdiff
path: root/Data/OpenPGP/Util/Ed25519.hs
blob: ed277c89f789c573203b27df400eda9e0005662b (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
50
51
module Data.OpenPGP.Util.Ed25519 where

import Crypto.Error
import qualified Crypto.PubKey.Ed25519 as Ed25519
import Data.OpenPGP.Internal -- (integerToBS,integerToLE,getBigNumLE)
import qualified Data.OpenPGP as OpenPGP
import Crypto.ECC.Edwards25519

import qualified Data.ByteArray as BA
import Control.Monad
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BL
import Data.List
import Data.Int
import Data.Word
import Data.OpenPGP.Util.Base

import Text.Printf
import Numeric
import Data.Char
import System.IO

import Foreign.Ptr
import System.IO.Unsafe

import Crypto.Cipher.SBox

ed25519Key :: OpenPGP.Packet -> Maybe Ed25519.PublicKey
ed25519Key k = case Ed25519.publicKey $ integerToBS $ keyParam 'n' k of
    CryptoPassed ed25519 -> Just ed25519
    CryptoFailed err     -> Nothing

ed25519sig sig =
    let [OpenPGP.MPI r,OpenPGP.MPI s] = OpenPGP.signature sig
        -- rbs = BS.pack $ take 32 $ rbytes r ++ repeat 0
        -- sbs = BS.pack $ take 32 $ rbytes s ++ repeat 0
        rbs = let r' = integerToBS r in BS.replicate (32 - BS.length r') 0 <> r'
        sbs = let s' = integerToBS s in BS.replicate (32 - BS.length s') 0 <> s'
    in case Ed25519.signature (rbs <> sbs) of
        CryptoPassed sig -> Just sig
        CryptoFailed err -> Nothing

ed25519Verify :: OpenPGP.Packet -> BS.ByteString -> OpenPGP.Packet -> Maybe Bool
ed25519Verify sig over k = do
    let hashbs = hashBySymbol (OpenPGP.hash_algorithm sig) $ BL.fromChunks [over]
    guard $ 0x2B06010401DA470F01 == keyParam 'c' k -- Only Ed25519 curve.
    k' <- ed25519Key k -- SecretKeyPacket ???
    sig' <- ed25519sig sig
    let result = Ed25519.verify k' hashbs sig'
    Just result