{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Crypto.Secp256k1
(
Msg
, msg
, getMsg
, SecKey
, secKey
, getSecKey
, derivePubKey
, PubKey
, importPubKey
, exportPubKey
, Sig
, signMsg
, verifySig
, normalizeSig
, importSig
, exportSig
, CompactSig
, getCompactSig
, compactSig
, exportCompactSig
, importCompactSig
, Tweak
, tweak
, getTweak
, tweakAddSecKey
, tweakMulSecKey
, tweakAddPubKey
, tweakMulPubKey
, combinePubKeys
, tweakNegate
) where
import Control.DeepSeq (NFData)
import Control.Monad (replicateM, unless, (<=<))
import Crypto.Secp256k1.Internal
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Base16 as B16
import Data.Hashable (Hashable (..))
import Data.Maybe (fromJust, fromMaybe, isJust)
import Data.Serialize (Serialize (..), getByteString,
putByteString)
import Data.String (IsString (..))
import Data.String.Conversions (ConvertibleStrings, cs)
import Foreign (alloca, allocaArray, allocaBytes,
free, mallocBytes, nullFunPtr,
nullPtr, peek, poke, pokeArray)
import GHC.Generics (Generic)
import System.IO.Unsafe (unsafePerformIO)
import Test.QuickCheck (Arbitrary (..),
arbitraryBoundedRandom, suchThat)
import Text.Read (Lexeme (String), lexP, parens,
pfail, readPrec)
newtype PubKey = PubKey { PubKey -> ByteString
getPubKey :: ByteString }
deriving (PubKey -> PubKey -> Bool
(PubKey -> PubKey -> Bool)
-> (PubKey -> PubKey -> Bool) -> Eq PubKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PubKey -> PubKey -> Bool
$c/= :: PubKey -> PubKey -> Bool
== :: PubKey -> PubKey -> Bool
$c== :: PubKey -> PubKey -> Bool
Eq, (forall x. PubKey -> Rep PubKey x)
-> (forall x. Rep PubKey x -> PubKey) -> Generic PubKey
forall x. Rep PubKey x -> PubKey
forall x. PubKey -> Rep PubKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PubKey x -> PubKey
$cfrom :: forall x. PubKey -> Rep PubKey x
Generic, PubKey -> ()
(PubKey -> ()) -> NFData PubKey
forall a. (a -> ()) -> NFData a
rnf :: PubKey -> ()
$crnf :: PubKey -> ()
NFData)
newtype Msg = Msg { Msg -> ByteString
getMsg :: ByteString }
deriving (Msg -> Msg -> Bool
(Msg -> Msg -> Bool) -> (Msg -> Msg -> Bool) -> Eq Msg
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Msg -> Msg -> Bool
$c/= :: Msg -> Msg -> Bool
== :: Msg -> Msg -> Bool
$c== :: Msg -> Msg -> Bool
Eq, (forall x. Msg -> Rep Msg x)
-> (forall x. Rep Msg x -> Msg) -> Generic Msg
forall x. Rep Msg x -> Msg
forall x. Msg -> Rep Msg x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Msg x -> Msg
$cfrom :: forall x. Msg -> Rep Msg x
Generic, Msg -> ()
(Msg -> ()) -> NFData Msg
forall a. (a -> ()) -> NFData a
rnf :: Msg -> ()
$crnf :: Msg -> ()
NFData)
newtype Sig = Sig { Sig -> ByteString
getSig :: ByteString }
deriving (Sig -> Sig -> Bool
(Sig -> Sig -> Bool) -> (Sig -> Sig -> Bool) -> Eq Sig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Sig -> Sig -> Bool
$c/= :: Sig -> Sig -> Bool
== :: Sig -> Sig -> Bool
$c== :: Sig -> Sig -> Bool
Eq, (forall x. Sig -> Rep Sig x)
-> (forall x. Rep Sig x -> Sig) -> Generic Sig
forall x. Rep Sig x -> Sig
forall x. Sig -> Rep Sig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Sig x -> Sig
$cfrom :: forall x. Sig -> Rep Sig x
Generic, Sig -> ()
(Sig -> ()) -> NFData Sig
forall a. (a -> ()) -> NFData a
rnf :: Sig -> ()
$crnf :: Sig -> ()
NFData)
newtype SecKey = SecKey { SecKey -> ByteString
getSecKey :: ByteString }
deriving (SecKey -> SecKey -> Bool
(SecKey -> SecKey -> Bool)
-> (SecKey -> SecKey -> Bool) -> Eq SecKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SecKey -> SecKey -> Bool
$c/= :: SecKey -> SecKey -> Bool
== :: SecKey -> SecKey -> Bool
$c== :: SecKey -> SecKey -> Bool
Eq, (forall x. SecKey -> Rep SecKey x)
-> (forall x. Rep SecKey x -> SecKey) -> Generic SecKey
forall x. Rep SecKey x -> SecKey
forall x. SecKey -> Rep SecKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SecKey x -> SecKey
$cfrom :: forall x. SecKey -> Rep SecKey x
Generic, SecKey -> ()
(SecKey -> ()) -> NFData SecKey
forall a. (a -> ()) -> NFData a
rnf :: SecKey -> ()
$crnf :: SecKey -> ()
NFData)
newtype Tweak = Tweak { Tweak -> ByteString
getTweak :: ByteString }
deriving (Tweak -> Tweak -> Bool
(Tweak -> Tweak -> Bool) -> (Tweak -> Tweak -> Bool) -> Eq Tweak
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Tweak -> Tweak -> Bool
$c/= :: Tweak -> Tweak -> Bool
== :: Tweak -> Tweak -> Bool
$c== :: Tweak -> Tweak -> Bool
Eq, (forall x. Tweak -> Rep Tweak x)
-> (forall x. Rep Tweak x -> Tweak) -> Generic Tweak
forall x. Rep Tweak x -> Tweak
forall x. Tweak -> Rep Tweak x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Tweak x -> Tweak
$cfrom :: forall x. Tweak -> Rep Tweak x
Generic, Tweak -> ()
(Tweak -> ()) -> NFData Tweak
forall a. (a -> ()) -> NFData a
rnf :: Tweak -> ()
$crnf :: Tweak -> ()
NFData)
newtype CompactSig = CompactSig { CompactSig -> ByteString
getCompactSig :: ByteString }
deriving (CompactSig -> CompactSig -> Bool
(CompactSig -> CompactSig -> Bool)
-> (CompactSig -> CompactSig -> Bool) -> Eq CompactSig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CompactSig -> CompactSig -> Bool
$c/= :: CompactSig -> CompactSig -> Bool
== :: CompactSig -> CompactSig -> Bool
$c== :: CompactSig -> CompactSig -> Bool
Eq, (forall x. CompactSig -> Rep CompactSig x)
-> (forall x. Rep CompactSig x -> CompactSig) -> Generic CompactSig
forall x. Rep CompactSig x -> CompactSig
forall x. CompactSig -> Rep CompactSig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CompactSig x -> CompactSig
$cfrom :: forall x. CompactSig -> Rep CompactSig x
Generic, CompactSig -> ()
(CompactSig -> ()) -> NFData CompactSig
forall a. (a -> ()) -> NFData a
rnf :: CompactSig -> ()
$crnf :: CompactSig -> ()
NFData)
instance Serialize PubKey where
put :: Putter PubKey
put (PubKey bs :: ByteString
bs) = Putter ByteString
putByteString ByteString
bs
get :: Get PubKey
get = ByteString -> PubKey
PubKey (ByteString -> PubKey) -> Get ByteString -> Get PubKey
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get ByteString
getByteString 64
instance Serialize Msg where
put :: Putter Msg
put (Msg m :: ByteString
m) = Putter ByteString
putByteString ByteString
m
get :: Get Msg
get = ByteString -> Msg
Msg (ByteString -> Msg) -> Get ByteString -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get ByteString
getByteString 32
instance Serialize Sig where
put :: Putter Sig
put (Sig bs :: ByteString
bs) = Putter ByteString
putByteString ByteString
bs
get :: Get Sig
get = ByteString -> Sig
Sig (ByteString -> Sig) -> Get ByteString -> Get Sig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get ByteString
getByteString 64
instance Serialize SecKey where
put :: Putter SecKey
put (SecKey bs :: ByteString
bs) = Putter ByteString
putByteString ByteString
bs
get :: Get SecKey
get = ByteString -> SecKey
SecKey (ByteString -> SecKey) -> Get ByteString -> Get SecKey
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get ByteString
getByteString 32
instance Serialize Tweak where
put :: Putter Tweak
put (Tweak bs :: ByteString
bs) = Putter ByteString
putByteString ByteString
bs
get :: Get Tweak
get = ByteString -> Tweak
Tweak (ByteString -> Tweak) -> Get ByteString -> Get Tweak
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get ByteString
getByteString 32
instance Serialize CompactSig where
put :: Putter CompactSig
put (CompactSig bs :: ByteString
bs) = Putter ByteString
putByteString ByteString
bs
get :: Get CompactSig
get = ByteString -> CompactSig
CompactSig (ByteString -> CompactSig) -> Get ByteString -> Get CompactSig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get ByteString
getByteString 64
decodeHex :: ConvertibleStrings a ByteString => a -> Maybe ByteString
decodeHex :: a -> Maybe ByteString
decodeHex str :: a
str = case ByteString -> Either Text ByteString
B16.decodeBase16 (ByteString -> Either Text ByteString)
-> ByteString -> Either Text ByteString
forall a b. (a -> b) -> a -> b
$ a -> ByteString
forall a b. ConvertibleStrings a b => a -> b
cs a
str of
Right bs :: ByteString
bs -> ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
bs
Left _ -> Maybe ByteString
forall a. Maybe a
Nothing
instance Read PubKey where
readPrec :: ReadPrec PubKey
readPrec = do
String str :: String
str <- ReadPrec Lexeme
lexP
ReadPrec PubKey
-> (PubKey -> ReadPrec PubKey) -> Maybe PubKey -> ReadPrec PubKey
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ReadPrec PubKey
forall a. ReadPrec a
pfail PubKey -> ReadPrec PubKey
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe PubKey -> ReadPrec PubKey)
-> Maybe PubKey -> ReadPrec PubKey
forall a b. (a -> b) -> a -> b
$ ByteString -> Maybe PubKey
importPubKey (ByteString -> Maybe PubKey) -> Maybe ByteString -> Maybe PubKey
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> Maybe ByteString
forall a. ConvertibleStrings a ByteString => a -> Maybe ByteString
decodeHex String
str
instance Hashable PubKey where
i :: Int
i hashWithSalt :: Int -> PubKey -> Int
`hashWithSalt` k :: PubKey
k = Int
i Int -> ByteString -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Bool -> PubKey -> ByteString
exportPubKey Bool
True PubKey
k
instance IsString PubKey where
fromString :: String -> PubKey
fromString = PubKey -> Maybe PubKey -> PubKey
forall a. a -> Maybe a -> a
fromMaybe PubKey
forall a. a
e (Maybe PubKey -> PubKey)
-> (String -> Maybe PubKey) -> String -> PubKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> Maybe PubKey
importPubKey (ByteString -> Maybe PubKey)
-> (String -> Maybe ByteString) -> String -> Maybe PubKey
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< String -> Maybe ByteString
forall a. ConvertibleStrings a ByteString => a -> Maybe ByteString
decodeHex) where
e :: a
e = String -> a
forall a. HasCallStack => String -> a
error "Could not decode public key from hex string"
instance Show PubKey where
showsPrec :: Int -> PubKey -> ShowS
showsPrec _ = Text -> ShowS
forall a. Show a => a -> ShowS
shows (Text -> ShowS) -> (PubKey -> Text) -> PubKey -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
B16.encodeBase16 (ByteString -> Text) -> (PubKey -> ByteString) -> PubKey -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> PubKey -> ByteString
exportPubKey Bool
True
instance Read Msg where
readPrec :: ReadPrec Msg
readPrec = ReadPrec Msg -> ReadPrec Msg
forall a. ReadPrec a -> ReadPrec a
parens (ReadPrec Msg -> ReadPrec Msg) -> ReadPrec Msg -> ReadPrec Msg
forall a b. (a -> b) -> a -> b
$ do
String str :: String
str <- ReadPrec Lexeme
lexP
ReadPrec Msg -> (Msg -> ReadPrec Msg) -> Maybe Msg -> ReadPrec Msg
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ReadPrec Msg
forall a. ReadPrec a
pfail Msg -> ReadPrec Msg
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Msg -> ReadPrec Msg) -> Maybe Msg -> ReadPrec Msg
forall a b. (a -> b) -> a -> b
$ ByteString -> Maybe Msg
msg (ByteString -> Maybe Msg) -> Maybe ByteString -> Maybe Msg
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> Maybe ByteString
forall a. ConvertibleStrings a ByteString => a -> Maybe ByteString
decodeHex String
str
instance Hashable Msg where
i :: Int
i hashWithSalt :: Int -> Msg -> Int
`hashWithSalt` m :: Msg
m = Int
i Int -> ByteString -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Msg -> ByteString
getMsg Msg
m
instance IsString Msg where
fromString :: String -> Msg
fromString = Msg -> Maybe Msg -> Msg
forall a. a -> Maybe a -> a
fromMaybe Msg
forall a. a
e (Maybe Msg -> Msg) -> (String -> Maybe Msg) -> String -> Msg
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> Maybe Msg
msg (ByteString -> Maybe Msg)
-> (String -> Maybe ByteString) -> String -> Maybe Msg
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< String -> Maybe ByteString
forall a. ConvertibleStrings a ByteString => a -> Maybe ByteString
decodeHex) where
e :: a
e = String -> a
forall a. HasCallStack => String -> a
error "Could not decode message from hex string"
instance Show Msg where
showsPrec :: Int -> Msg -> ShowS
showsPrec _ = Text -> ShowS
forall a. Show a => a -> ShowS
shows (Text -> ShowS) -> (Msg -> Text) -> Msg -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
B16.encodeBase16 (ByteString -> Text) -> (Msg -> ByteString) -> Msg -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Msg -> ByteString
getMsg
instance Read Sig where
readPrec :: ReadPrec Sig
readPrec = ReadPrec Sig -> ReadPrec Sig
forall a. ReadPrec a -> ReadPrec a
parens (ReadPrec Sig -> ReadPrec Sig) -> ReadPrec Sig -> ReadPrec Sig
forall a b. (a -> b) -> a -> b
$ do
String str :: String
str <- ReadPrec Lexeme
lexP
ReadPrec Sig -> (Sig -> ReadPrec Sig) -> Maybe Sig -> ReadPrec Sig
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ReadPrec Sig
forall a. ReadPrec a
pfail Sig -> ReadPrec Sig
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Sig -> ReadPrec Sig) -> Maybe Sig -> ReadPrec Sig
forall a b. (a -> b) -> a -> b
$ ByteString -> Maybe Sig
importSig (ByteString -> Maybe Sig) -> Maybe ByteString -> Maybe Sig
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> Maybe ByteString
forall a. ConvertibleStrings a ByteString => a -> Maybe ByteString
decodeHex String
str
instance IsString Sig where
fromString :: String -> Sig
fromString = Sig -> Maybe Sig -> Sig
forall a. a -> Maybe a -> a
fromMaybe Sig
forall a. a
e (Maybe Sig -> Sig) -> (String -> Maybe Sig) -> String -> Sig
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> Maybe Sig
importSig (ByteString -> Maybe Sig)
-> (String -> Maybe ByteString) -> String -> Maybe Sig
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< String -> Maybe ByteString
forall a. ConvertibleStrings a ByteString => a -> Maybe ByteString
decodeHex) where
e :: a
e = String -> a
forall a. HasCallStack => String -> a
error "Could not decode signature from hex string"
instance Hashable Sig where
i :: Int
i hashWithSalt :: Int -> Sig -> Int
`hashWithSalt` s :: Sig
s = Int
i Int -> ByteString -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Sig -> ByteString
exportSig Sig
s
instance Show Sig where
showsPrec :: Int -> Sig -> ShowS
showsPrec _ = Text -> ShowS
forall a. Show a => a -> ShowS
shows (Text -> ShowS) -> (Sig -> Text) -> Sig -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
B16.encodeBase16 (ByteString -> Text) -> (Sig -> ByteString) -> Sig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sig -> ByteString
exportSig
instance Read SecKey where
readPrec :: ReadPrec SecKey
readPrec = ReadPrec SecKey -> ReadPrec SecKey
forall a. ReadPrec a -> ReadPrec a
parens (ReadPrec SecKey -> ReadPrec SecKey)
-> ReadPrec SecKey -> ReadPrec SecKey
forall a b. (a -> b) -> a -> b
$ do
String str :: String
str <- ReadPrec Lexeme
lexP
ReadPrec SecKey
-> (SecKey -> ReadPrec SecKey) -> Maybe SecKey -> ReadPrec SecKey
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ReadPrec SecKey
forall a. ReadPrec a
pfail SecKey -> ReadPrec SecKey
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe SecKey -> ReadPrec SecKey)
-> Maybe SecKey -> ReadPrec SecKey
forall a b. (a -> b) -> a -> b
$ ByteString -> Maybe SecKey
secKey (ByteString -> Maybe SecKey) -> Maybe ByteString -> Maybe SecKey
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> Maybe ByteString
forall a. ConvertibleStrings a ByteString => a -> Maybe ByteString
decodeHex String
str
instance Hashable SecKey where
i :: Int
i hashWithSalt :: Int -> SecKey -> Int
`hashWithSalt` k :: SecKey
k = Int
i Int -> ByteString -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` SecKey -> ByteString
getSecKey SecKey
k
instance IsString SecKey where
fromString :: String -> SecKey
fromString = SecKey -> Maybe SecKey -> SecKey
forall a. a -> Maybe a -> a
fromMaybe SecKey
forall a. a
e (Maybe SecKey -> SecKey)
-> (String -> Maybe SecKey) -> String -> SecKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> Maybe SecKey
secKey (ByteString -> Maybe SecKey)
-> (String -> Maybe ByteString) -> String -> Maybe SecKey
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< String -> Maybe ByteString
forall a. ConvertibleStrings a ByteString => a -> Maybe ByteString
decodeHex) where
e :: a
e = String -> a
forall a. HasCallStack => String -> a
error "Colud not decode secret key from hex string"
instance Show SecKey where
showsPrec :: Int -> SecKey -> ShowS
showsPrec _ = Text -> ShowS
forall a. Show a => a -> ShowS
shows (Text -> ShowS) -> (SecKey -> Text) -> SecKey -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
B16.encodeBase16 (ByteString -> Text) -> (SecKey -> ByteString) -> SecKey -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SecKey -> ByteString
getSecKey
instance Hashable Tweak where
i :: Int
i hashWithSalt :: Int -> Tweak -> Int
`hashWithSalt` t :: Tweak
t = Int
i Int -> ByteString -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Tweak -> ByteString
getTweak Tweak
t
instance Read Tweak where
readPrec :: ReadPrec Tweak
readPrec = ReadPrec Tweak -> ReadPrec Tweak
forall a. ReadPrec a -> ReadPrec a
parens (ReadPrec Tweak -> ReadPrec Tweak)
-> ReadPrec Tweak -> ReadPrec Tweak
forall a b. (a -> b) -> a -> b
$ do
String str :: String
str <- ReadPrec Lexeme
lexP
ReadPrec Tweak
-> (Tweak -> ReadPrec Tweak) -> Maybe Tweak -> ReadPrec Tweak
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ReadPrec Tweak
forall a. ReadPrec a
pfail Tweak -> ReadPrec Tweak
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Tweak -> ReadPrec Tweak) -> Maybe Tweak -> ReadPrec Tweak
forall a b. (a -> b) -> a -> b
$ ByteString -> Maybe Tweak
tweak (ByteString -> Maybe Tweak) -> Maybe ByteString -> Maybe Tweak
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> Maybe ByteString
forall a. ConvertibleStrings a ByteString => a -> Maybe ByteString
decodeHex String
str
instance IsString Tweak where
fromString :: String -> Tweak
fromString = Tweak -> Maybe Tweak -> Tweak
forall a. a -> Maybe a -> a
fromMaybe Tweak
forall a. a
e (Maybe Tweak -> Tweak)
-> (String -> Maybe Tweak) -> String -> Tweak
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> Maybe Tweak
tweak (ByteString -> Maybe Tweak)
-> (String -> Maybe ByteString) -> String -> Maybe Tweak
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< String -> Maybe ByteString
forall a. ConvertibleStrings a ByteString => a -> Maybe ByteString
decodeHex) where
e :: a
e = String -> a
forall a. HasCallStack => String -> a
error "Could not decode tweak from hex string"
instance Show Tweak where
showsPrec :: Int -> Tweak -> ShowS
showsPrec _ = Text -> ShowS
forall a. Show a => a -> ShowS
shows (Text -> ShowS) -> (Tweak -> Text) -> Tweak -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
B16.encodeBase16 (ByteString -> Text) -> (Tweak -> ByteString) -> Tweak -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tweak -> ByteString
getTweak
msg :: ByteString -> Maybe Msg
msg :: ByteString -> Maybe Msg
msg bs :: ByteString
bs
| ByteString -> Int
BS.length ByteString
bs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== 32 = Msg -> Maybe Msg
forall a. a -> Maybe a
Just (ByteString -> Msg
Msg ByteString
bs)
| Bool
otherwise = Maybe Msg
forall a. Maybe a
Nothing
secKey :: ByteString -> Maybe SecKey
secKey :: ByteString -> Maybe SecKey
secKey bs :: ByteString
bs
| ByteString -> Int
BS.length ByteString
bs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== 32 = SecKey -> Maybe SecKey
forall a. a -> Maybe a
Just (ByteString -> SecKey
SecKey ByteString
bs)
| Bool
otherwise = Maybe SecKey
forall a. Maybe a
Nothing
compactSig :: ByteString -> Maybe CompactSig
compactSig :: ByteString -> Maybe CompactSig
compactSig bs :: ByteString
bs
| ByteString -> Int
BS.length ByteString
bs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== 64 = CompactSig -> Maybe CompactSig
forall a. a -> Maybe a
Just (ByteString -> CompactSig
CompactSig ByteString
bs)
| Bool
otherwise = Maybe CompactSig
forall a. Maybe a
Nothing
normalizeSig :: Sig -> Maybe Sig
normalizeSig :: Sig -> Maybe Sig
normalizeSig (Sig sig :: ByteString
sig) = IO (Maybe Sig) -> Maybe Sig
forall a. IO a -> a
unsafePerformIO (IO (Maybe Sig) -> Maybe Sig) -> IO (Maybe Sig) -> Maybe Sig
forall a b. (a -> b) -> a -> b
$
ByteString
-> ((Ptr Sig64, CSize) -> IO (Maybe Sig)) -> IO (Maybe Sig)
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
unsafeUseByteString ByteString
sig (((Ptr Sig64, CSize) -> IO (Maybe Sig)) -> IO (Maybe Sig))
-> ((Ptr Sig64, CSize) -> IO (Maybe Sig)) -> IO (Maybe Sig)
forall a b. (a -> b) -> a -> b
$ \(sig_in :: Ptr Sig64
sig_in, _) -> do
Ptr Sig64
sig_out <- Int -> IO (Ptr Sig64)
forall a. Int -> IO (Ptr a)
mallocBytes 64
Ret
ret <- Ctx -> Ptr Sig64 -> Ptr Sig64 -> IO Ret
ecdsaSignatureNormalize Ctx
ctx Ptr Sig64
sig_out Ptr Sig64
sig_in
if Ret -> Bool
isSuccess Ret
ret
then do
ByteString
bs <- (Ptr Sig64, CSize) -> IO ByteString
forall a. (Ptr a, CSize) -> IO ByteString
unsafePackByteString (Ptr Sig64
sig_out, 64)
Maybe Sig -> IO (Maybe Sig)
forall (m :: * -> *) a. Monad m => a -> m a
return (Sig -> Maybe Sig
forall a. a -> Maybe a
Just (ByteString -> Sig
Sig ByteString
bs))
else do
Ptr Sig64 -> IO ()
forall a. Ptr a -> IO ()
free Ptr Sig64
sig_out
Maybe Sig -> IO (Maybe Sig)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Sig
forall a. Maybe a
Nothing
tweak :: ByteString -> Maybe Tweak
tweak :: ByteString -> Maybe Tweak
tweak bs :: ByteString
bs
| ByteString -> Int
BS.length ByteString
bs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== 32 = Tweak -> Maybe Tweak
forall a. a -> Maybe a
Just (ByteString -> Tweak
Tweak ByteString
bs)
| Bool
otherwise = Maybe Tweak
forall a. Maybe a
Nothing
importPubKey :: ByteString -> Maybe PubKey
importPubKey :: ByteString -> Maybe PubKey
importPubKey bs :: ByteString
bs
| ByteString -> Bool
BS.null ByteString
bs = Maybe PubKey
forall a. Maybe a
Nothing
| Bool
otherwise = IO (Maybe PubKey) -> Maybe PubKey
forall a. IO a -> a
unsafePerformIO (IO (Maybe PubKey) -> Maybe PubKey)
-> IO (Maybe PubKey) -> Maybe PubKey
forall a b. (a -> b) -> a -> b
$
ByteString
-> ((Ptr CUChar, CSize) -> IO (Maybe PubKey)) -> IO (Maybe PubKey)
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
unsafeUseByteString ByteString
bs (((Ptr CUChar, CSize) -> IO (Maybe PubKey)) -> IO (Maybe PubKey))
-> ((Ptr CUChar, CSize) -> IO (Maybe PubKey)) -> IO (Maybe PubKey)
forall a b. (a -> b) -> a -> b
$ \(input :: Ptr CUChar
input, len :: CSize
len) -> do
Ptr PubKey64
pub_key <- Int -> IO (Ptr PubKey64)
forall a. Int -> IO (Ptr a)
mallocBytes 64
Ret
ret <- Ctx -> Ptr PubKey64 -> Ptr CUChar -> CSize -> IO Ret
ecPubKeyParse Ctx
ctx Ptr PubKey64
pub_key Ptr CUChar
input CSize
len
if Ret -> Bool
isSuccess Ret
ret
then do
ByteString
out <- (Ptr PubKey64, CSize) -> IO ByteString
forall a. (Ptr a, CSize) -> IO ByteString
unsafePackByteString (Ptr PubKey64
pub_key, 64)
Maybe PubKey -> IO (Maybe PubKey)
forall (m :: * -> *) a. Monad m => a -> m a
return (PubKey -> Maybe PubKey
forall a. a -> Maybe a
Just (ByteString -> PubKey
PubKey ByteString
out))
else do
Ptr PubKey64 -> IO ()
forall a. Ptr a -> IO ()
free Ptr PubKey64
pub_key
Maybe PubKey -> IO (Maybe PubKey)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PubKey
forall a. Maybe a
Nothing
exportPubKey :: Bool -> PubKey -> ByteString
exportPubKey :: Bool -> PubKey -> ByteString
exportPubKey compress :: Bool
compress (PubKey in_bs :: ByteString
in_bs) = IO ByteString -> ByteString
forall a. IO a -> a
unsafePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$
ByteString
-> ((Ptr PubKey64, CSize) -> IO ByteString) -> IO ByteString
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
unsafeUseByteString ByteString
in_bs (((Ptr PubKey64, CSize) -> IO ByteString) -> IO ByteString)
-> ((Ptr PubKey64, CSize) -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \(in_ptr :: Ptr PubKey64
in_ptr, _) ->
(Ptr CSize -> IO ByteString) -> IO ByteString
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CSize -> IO ByteString) -> IO ByteString)
-> (Ptr CSize -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \len_ptr :: Ptr CSize
len_ptr ->
Int -> (Ptr CUChar -> IO ByteString) -> IO ByteString
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
len ((Ptr CUChar -> IO ByteString) -> IO ByteString)
-> (Ptr CUChar -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \out_ptr :: Ptr CUChar
out_ptr -> do
Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr CSize
len_ptr (CSize -> IO ()) -> CSize -> IO ()
forall a b. (a -> b) -> a -> b
$ Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len
Ret
ret <- Ctx
-> Ptr CUChar -> Ptr CSize -> Ptr PubKey64 -> SerFlags -> IO Ret
ecPubKeySerialize Ctx
ctx Ptr CUChar
out_ptr Ptr CSize
len_ptr Ptr PubKey64
in_ptr SerFlags
flags
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Ret -> Bool
isSuccess Ret
ret) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO ()
forall a. HasCallStack => String -> a
error "could not serialize public key"
CSize
final_len <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek Ptr CSize
len_ptr
(Ptr CUChar, CSize) -> IO ByteString
forall a. (Ptr a, CSize) -> IO ByteString
packByteString (Ptr CUChar
out_ptr, CSize
final_len)
where
len :: Int
len = if Bool
compress then 33 else 65
flags :: SerFlags
flags = if Bool
compress then SerFlags
compressed else SerFlags
uncompressed
exportCompactSig :: Sig -> CompactSig
exportCompactSig :: Sig -> CompactSig
exportCompactSig (Sig sig_bs :: ByteString
sig_bs) = IO CompactSig -> CompactSig
forall a. IO a -> a
unsafePerformIO (IO CompactSig -> CompactSig) -> IO CompactSig -> CompactSig
forall a b. (a -> b) -> a -> b
$
ByteString
-> ((Ptr Sig64, CSize) -> IO CompactSig) -> IO CompactSig
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
unsafeUseByteString ByteString
sig_bs (((Ptr Sig64, CSize) -> IO CompactSig) -> IO CompactSig)
-> ((Ptr Sig64, CSize) -> IO CompactSig) -> IO CompactSig
forall a b. (a -> b) -> a -> b
$ \(sig_ptr :: Ptr Sig64
sig_ptr, _) -> do
Ptr Compact64
out_ptr <- Int -> IO (Ptr Compact64)
forall a. Int -> IO (Ptr a)
mallocBytes 64
Ret
ret <- Ctx -> Ptr Compact64 -> Ptr Sig64 -> IO Ret
ecdsaSignatureSerializeCompact Ctx
ctx Ptr Compact64
out_ptr Ptr Sig64
sig_ptr
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Ret -> Bool
isSuccess Ret
ret) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Compact64 -> IO ()
forall a. Ptr a -> IO ()
free Ptr Compact64
out_ptr
String -> IO ()
forall a. HasCallStack => String -> a
error "Could not obtain compact signature"
ByteString
out_bs <- (Ptr Compact64, CSize) -> IO ByteString
forall a. (Ptr a, CSize) -> IO ByteString
unsafePackByteString (Ptr Compact64
out_ptr, 64)
CompactSig -> IO CompactSig
forall (m :: * -> *) a. Monad m => a -> m a
return (CompactSig -> IO CompactSig) -> CompactSig -> IO CompactSig
forall a b. (a -> b) -> a -> b
$ ByteString -> CompactSig
CompactSig ByteString
out_bs
importCompactSig :: CompactSig -> Maybe Sig
importCompactSig :: CompactSig -> Maybe Sig
importCompactSig (CompactSig compact_sig :: ByteString
compact_sig) = IO (Maybe Sig) -> Maybe Sig
forall a. IO a -> a
unsafePerformIO (IO (Maybe Sig) -> Maybe Sig) -> IO (Maybe Sig) -> Maybe Sig
forall a b. (a -> b) -> a -> b
$
ByteString
-> ((Ptr Compact64, CSize) -> IO (Maybe Sig)) -> IO (Maybe Sig)
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
unsafeUseByteString ByteString
compact_sig (((Ptr Compact64, CSize) -> IO (Maybe Sig)) -> IO (Maybe Sig))
-> ((Ptr Compact64, CSize) -> IO (Maybe Sig)) -> IO (Maybe Sig)
forall a b. (a -> b) -> a -> b
$ \(compact_ptr :: Ptr Compact64
compact_ptr, _) -> do
Ptr Sig64
out_sig <- Int -> IO (Ptr Sig64)
forall a. Int -> IO (Ptr a)
mallocBytes 64
Ret
ret <- Ctx -> Ptr Sig64 -> Ptr Compact64 -> IO Ret
ecdsaSignatureParseCompact Ctx
ctx Ptr Sig64
out_sig Ptr Compact64
compact_ptr
if Ret -> Bool
isSuccess Ret
ret
then do
ByteString
out_bs <- (Ptr Sig64, CSize) -> IO ByteString
forall a. (Ptr a, CSize) -> IO ByteString
unsafePackByteString (Ptr Sig64
out_sig, 64)
Maybe Sig -> IO (Maybe Sig)
forall (m :: * -> *) a. Monad m => a -> m a
return (Sig -> Maybe Sig
forall a. a -> Maybe a
Just (ByteString -> Sig
Sig ByteString
out_bs))
else do
Ptr Sig64 -> IO ()
forall a. Ptr a -> IO ()
free Ptr Sig64
out_sig
Maybe Sig -> IO (Maybe Sig)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Sig
forall a. Maybe a
Nothing
importSig :: ByteString -> Maybe Sig
importSig :: ByteString -> Maybe Sig
importSig bs :: ByteString
bs
| ByteString -> Bool
BS.null ByteString
bs = Maybe Sig
forall a. Maybe a
Nothing
| Bool
otherwise = IO (Maybe Sig) -> Maybe Sig
forall a. IO a -> a
unsafePerformIO (IO (Maybe Sig) -> Maybe Sig) -> IO (Maybe Sig) -> Maybe Sig
forall a b. (a -> b) -> a -> b
$
ByteString
-> ((Ptr CUChar, CSize) -> IO (Maybe Sig)) -> IO (Maybe Sig)
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
unsafeUseByteString ByteString
bs (((Ptr CUChar, CSize) -> IO (Maybe Sig)) -> IO (Maybe Sig))
-> ((Ptr CUChar, CSize) -> IO (Maybe Sig)) -> IO (Maybe Sig)
forall a b. (a -> b) -> a -> b
$ \(in_ptr :: Ptr CUChar
in_ptr, in_len :: CSize
in_len) -> do
Ptr Sig64
out_sig <- Int -> IO (Ptr Sig64)
forall a. Int -> IO (Ptr a)
mallocBytes 64
Ret
ret <- Ctx -> Ptr Sig64 -> Ptr CUChar -> CSize -> IO Ret
ecdsaSignatureParseDer Ctx
ctx Ptr Sig64
out_sig Ptr CUChar
in_ptr CSize
in_len
if Ret -> Bool
isSuccess Ret
ret
then do
ByteString
out_bs <- (Ptr Sig64, CSize) -> IO ByteString
forall a. (Ptr a, CSize) -> IO ByteString
unsafePackByteString (Ptr Sig64
out_sig, 64)
Maybe Sig -> IO (Maybe Sig)
forall (m :: * -> *) a. Monad m => a -> m a
return (Sig -> Maybe Sig
forall a. a -> Maybe a
Just (ByteString -> Sig
Sig ByteString
out_bs))
else do
Ptr Sig64 -> IO ()
forall a. Ptr a -> IO ()
free Ptr Sig64
out_sig
Maybe Sig -> IO (Maybe Sig)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Sig
forall a. Maybe a
Nothing
exportSig :: Sig -> ByteString
exportSig :: Sig -> ByteString
exportSig (Sig in_sig :: ByteString
in_sig) = IO ByteString -> ByteString
forall a. IO a -> a
unsafePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$
ByteString
-> ((Ptr Sig64, CSize) -> IO ByteString) -> IO ByteString
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
unsafeUseByteString ByteString
in_sig (((Ptr Sig64, CSize) -> IO ByteString) -> IO ByteString)
-> ((Ptr Sig64, CSize) -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \(in_ptr :: Ptr Sig64
in_ptr, _) ->
(Ptr CSize -> IO ByteString) -> IO ByteString
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CSize -> IO ByteString) -> IO ByteString)
-> (Ptr CSize -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \out_len :: Ptr CSize
out_len ->
Int -> (Ptr CUChar -> IO ByteString) -> IO ByteString
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes 72 ((Ptr CUChar -> IO ByteString) -> IO ByteString)
-> (Ptr CUChar -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \out_ptr :: Ptr CUChar
out_ptr -> do
Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr CSize
out_len 72
Ret
ret <- Ctx -> Ptr CUChar -> Ptr CSize -> Ptr Sig64 -> IO Ret
ecdsaSignatureSerializeDer Ctx
ctx Ptr CUChar
out_ptr Ptr CSize
out_len Ptr Sig64
in_ptr
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Ret -> Bool
isSuccess Ret
ret) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO ()
forall a. HasCallStack => String -> a
error "could not serialize signature"
CSize
final_len <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek Ptr CSize
out_len
(Ptr CUChar, CSize) -> IO ByteString
forall a. (Ptr a, CSize) -> IO ByteString
packByteString (Ptr CUChar
out_ptr, CSize
final_len)
verifySig :: PubKey -> Sig -> Msg -> Bool
verifySig :: PubKey -> Sig -> Msg -> Bool
verifySig (PubKey pub_key :: ByteString
pub_key) (Sig sig :: ByteString
sig) (Msg m :: ByteString
m) = IO Bool -> Bool
forall a. IO a -> a
unsafePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$
ByteString -> ((Ptr PubKey64, CSize) -> IO Bool) -> IO Bool
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
unsafeUseByteString ByteString
pub_key (((Ptr PubKey64, CSize) -> IO Bool) -> IO Bool)
-> ((Ptr PubKey64, CSize) -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \(pub_key_ptr :: Ptr PubKey64
pub_key_ptr, _) ->
ByteString -> ((Ptr Sig64, CSize) -> IO Bool) -> IO Bool
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
unsafeUseByteString ByteString
sig (((Ptr Sig64, CSize) -> IO Bool) -> IO Bool)
-> ((Ptr Sig64, CSize) -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \(sig_ptr :: Ptr Sig64
sig_ptr, _) ->
ByteString -> ((Ptr Msg32, CSize) -> IO Bool) -> IO Bool
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
unsafeUseByteString ByteString
m (((Ptr Msg32, CSize) -> IO Bool) -> IO Bool)
-> ((Ptr Msg32, CSize) -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \(msg_ptr :: Ptr Msg32
msg_ptr, _) ->
Ret -> Bool
isSuccess (Ret -> Bool) -> IO Ret -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ctx -> Ptr Sig64 -> Ptr Msg32 -> Ptr PubKey64 -> IO Ret
ecdsaVerify Ctx
ctx Ptr Sig64
sig_ptr Ptr Msg32
msg_ptr Ptr PubKey64
pub_key_ptr
signMsg :: SecKey -> Msg -> Sig
signMsg :: SecKey -> Msg -> Sig
signMsg (SecKey sec_key :: ByteString
sec_key) (Msg m :: ByteString
m) = IO Sig -> Sig
forall a. IO a -> a
unsafePerformIO (IO Sig -> Sig) -> IO Sig -> Sig
forall a b. (a -> b) -> a -> b
$
ByteString -> ((Ptr SecKey32, CSize) -> IO Sig) -> IO Sig
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
unsafeUseByteString ByteString
sec_key (((Ptr SecKey32, CSize) -> IO Sig) -> IO Sig)
-> ((Ptr SecKey32, CSize) -> IO Sig) -> IO Sig
forall a b. (a -> b) -> a -> b
$ \(sec_key_ptr :: Ptr SecKey32
sec_key_ptr, _) ->
ByteString -> ((Ptr Msg32, CSize) -> IO Sig) -> IO Sig
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
unsafeUseByteString ByteString
m (((Ptr Msg32, CSize) -> IO Sig) -> IO Sig)
-> ((Ptr Msg32, CSize) -> IO Sig) -> IO Sig
forall a b. (a -> b) -> a -> b
$ \(msg_ptr :: Ptr Msg32
msg_ptr, _) -> do
Ptr Sig64
sig_ptr <- Int -> IO (Ptr Sig64)
forall a. Int -> IO (Ptr a)
mallocBytes 64
Ret
ret <- Ctx
-> Ptr Sig64
-> Ptr Msg32
-> Ptr SecKey32
-> FunPtr (NonceFun Any)
-> Ptr Any
-> IO Ret
forall a.
Ctx
-> Ptr Sig64
-> Ptr Msg32
-> Ptr SecKey32
-> FunPtr (NonceFun a)
-> Ptr a
-> IO Ret
ecdsaSign Ctx
ctx Ptr Sig64
sig_ptr Ptr Msg32
msg_ptr Ptr SecKey32
sec_key_ptr FunPtr (NonceFun Any)
forall a. FunPtr a
nullFunPtr Ptr Any
forall a. Ptr a
nullPtr
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Ret -> Bool
isSuccess Ret
ret) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Sig64 -> IO ()
forall a. Ptr a -> IO ()
free Ptr Sig64
sig_ptr
String -> IO ()
forall a. HasCallStack => String -> a
error "could not sign message"
ByteString -> Sig
Sig (ByteString -> Sig) -> IO ByteString -> IO Sig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Ptr Sig64, CSize) -> IO ByteString
forall a. (Ptr a, CSize) -> IO ByteString
unsafePackByteString (Ptr Sig64
sig_ptr, 64)
derivePubKey :: SecKey -> PubKey
derivePubKey :: SecKey -> PubKey
derivePubKey (SecKey sec_key :: ByteString
sec_key) = IO PubKey -> PubKey
forall a. IO a -> a
unsafePerformIO (IO PubKey -> PubKey) -> IO PubKey -> PubKey
forall a b. (a -> b) -> a -> b
$
ByteString -> ((Ptr SecKey32, CSize) -> IO PubKey) -> IO PubKey
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
unsafeUseByteString ByteString
sec_key (((Ptr SecKey32, CSize) -> IO PubKey) -> IO PubKey)
-> ((Ptr SecKey32, CSize) -> IO PubKey) -> IO PubKey
forall a b. (a -> b) -> a -> b
$ \(sec_key_ptr :: Ptr SecKey32
sec_key_ptr, _) -> do
Ptr PubKey64
pub_key_ptr <- Int -> IO (Ptr PubKey64)
forall a. Int -> IO (Ptr a)
mallocBytes 64
Ret
ret <- Ctx -> Ptr PubKey64 -> Ptr SecKey32 -> IO Ret
ecPubKeyCreate Ctx
ctx Ptr PubKey64
pub_key_ptr Ptr SecKey32
sec_key_ptr
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Ret -> Bool
isSuccess Ret
ret) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Ptr PubKey64 -> IO ()
forall a. Ptr a -> IO ()
free Ptr PubKey64
pub_key_ptr
String -> IO ()
forall a. HasCallStack => String -> a
error "could not compute public key"
ByteString -> PubKey
PubKey (ByteString -> PubKey) -> IO ByteString -> IO PubKey
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Ptr PubKey64, CSize) -> IO ByteString
forall a. (Ptr a, CSize) -> IO ByteString
unsafePackByteString (Ptr PubKey64
pub_key_ptr, 64)
tweakAddSecKey :: SecKey -> Tweak -> Maybe SecKey
tweakAddSecKey :: SecKey -> Tweak -> Maybe SecKey
tweakAddSecKey (SecKey sec_key :: ByteString
sec_key) (Tweak t :: ByteString
t) = IO (Maybe SecKey) -> Maybe SecKey
forall a. IO a -> a
unsafePerformIO (IO (Maybe SecKey) -> Maybe SecKey)
-> IO (Maybe SecKey) -> Maybe SecKey
forall a b. (a -> b) -> a -> b
$
ByteString
-> ((Ptr SecKey32, CSize) -> IO (Maybe SecKey))
-> IO (Maybe SecKey)
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
unsafeUseByteString ByteString
new_bs (((Ptr SecKey32, CSize) -> IO (Maybe SecKey)) -> IO (Maybe SecKey))
-> ((Ptr SecKey32, CSize) -> IO (Maybe SecKey))
-> IO (Maybe SecKey)
forall a b. (a -> b) -> a -> b
$ \(sec_key_ptr :: Ptr SecKey32
sec_key_ptr, _) ->
ByteString
-> ((Ptr Tweak32, CSize) -> IO (Maybe SecKey)) -> IO (Maybe SecKey)
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
unsafeUseByteString ByteString
t (((Ptr Tweak32, CSize) -> IO (Maybe SecKey)) -> IO (Maybe SecKey))
-> ((Ptr Tweak32, CSize) -> IO (Maybe SecKey)) -> IO (Maybe SecKey)
forall a b. (a -> b) -> a -> b
$ \(tweak_ptr :: Ptr Tweak32
tweak_ptr, _) -> do
Ret
ret <- Ctx -> Ptr SecKey32 -> Ptr Tweak32 -> IO Ret
ecSecKeyTweakAdd Ctx
ctx Ptr SecKey32
sec_key_ptr Ptr Tweak32
tweak_ptr
if Ret -> Bool
isSuccess Ret
ret
then Maybe SecKey -> IO (Maybe SecKey)
forall (m :: * -> *) a. Monad m => a -> m a
return (SecKey -> Maybe SecKey
forall a. a -> Maybe a
Just (ByteString -> SecKey
SecKey ByteString
new_bs))
else Maybe SecKey -> IO (Maybe SecKey)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe SecKey
forall a. Maybe a
Nothing
where
new_bs :: ByteString
new_bs = ByteString -> ByteString
BS.copy ByteString
sec_key
tweakMulSecKey :: SecKey -> Tweak -> Maybe SecKey
tweakMulSecKey :: SecKey -> Tweak -> Maybe SecKey
tweakMulSecKey (SecKey sec_key :: ByteString
sec_key) (Tweak t :: ByteString
t) = IO (Maybe SecKey) -> Maybe SecKey
forall a. IO a -> a
unsafePerformIO (IO (Maybe SecKey) -> Maybe SecKey)
-> IO (Maybe SecKey) -> Maybe SecKey
forall a b. (a -> b) -> a -> b
$
ByteString
-> ((Ptr SecKey32, CSize) -> IO (Maybe SecKey))
-> IO (Maybe SecKey)
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
unsafeUseByteString ByteString
new_bs (((Ptr SecKey32, CSize) -> IO (Maybe SecKey)) -> IO (Maybe SecKey))
-> ((Ptr SecKey32, CSize) -> IO (Maybe SecKey))
-> IO (Maybe SecKey)
forall a b. (a -> b) -> a -> b
$ \(sec_key_ptr :: Ptr SecKey32
sec_key_ptr, _) ->
ByteString
-> ((Ptr Tweak32, CSize) -> IO (Maybe SecKey)) -> IO (Maybe SecKey)
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
unsafeUseByteString ByteString
t (((Ptr Tweak32, CSize) -> IO (Maybe SecKey)) -> IO (Maybe SecKey))
-> ((Ptr Tweak32, CSize) -> IO (Maybe SecKey)) -> IO (Maybe SecKey)
forall a b. (a -> b) -> a -> b
$ \(tweak_ptr :: Ptr Tweak32
tweak_ptr, _) -> do
Ret
ret <- Ctx -> Ptr SecKey32 -> Ptr Tweak32 -> IO Ret
ecSecKeyTweakMul Ctx
ctx Ptr SecKey32
sec_key_ptr Ptr Tweak32
tweak_ptr
if Ret -> Bool
isSuccess Ret
ret
then Maybe SecKey -> IO (Maybe SecKey)
forall (m :: * -> *) a. Monad m => a -> m a
return (SecKey -> Maybe SecKey
forall a. a -> Maybe a
Just (ByteString -> SecKey
SecKey ByteString
new_bs))
else Maybe SecKey -> IO (Maybe SecKey)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe SecKey
forall a. Maybe a
Nothing
where
new_bs :: ByteString
new_bs = ByteString -> ByteString
BS.copy ByteString
sec_key
tweakAddPubKey :: PubKey -> Tweak -> Maybe PubKey
tweakAddPubKey :: PubKey -> Tweak -> Maybe PubKey
tweakAddPubKey (PubKey pub_key :: ByteString
pub_key) (Tweak t :: ByteString
t) = IO (Maybe PubKey) -> Maybe PubKey
forall a. IO a -> a
unsafePerformIO (IO (Maybe PubKey) -> Maybe PubKey)
-> IO (Maybe PubKey) -> Maybe PubKey
forall a b. (a -> b) -> a -> b
$
ByteString
-> ((Ptr PubKey64, CSize) -> IO (Maybe PubKey))
-> IO (Maybe PubKey)
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
unsafeUseByteString ByteString
new_bs (((Ptr PubKey64, CSize) -> IO (Maybe PubKey)) -> IO (Maybe PubKey))
-> ((Ptr PubKey64, CSize) -> IO (Maybe PubKey))
-> IO (Maybe PubKey)
forall a b. (a -> b) -> a -> b
$ \(pub_key_ptr :: Ptr PubKey64
pub_key_ptr, _) ->
ByteString
-> ((Ptr Tweak32, CSize) -> IO (Maybe PubKey)) -> IO (Maybe PubKey)
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
unsafeUseByteString ByteString
t (((Ptr Tweak32, CSize) -> IO (Maybe PubKey)) -> IO (Maybe PubKey))
-> ((Ptr Tweak32, CSize) -> IO (Maybe PubKey)) -> IO (Maybe PubKey)
forall a b. (a -> b) -> a -> b
$ \(tweak_ptr :: Ptr Tweak32
tweak_ptr, _) -> do
Ret
ret <- Ctx -> Ptr PubKey64 -> Ptr Tweak32 -> IO Ret
ecPubKeyTweakAdd Ctx
ctx Ptr PubKey64
pub_key_ptr Ptr Tweak32
tweak_ptr
if Ret -> Bool
isSuccess Ret
ret
then Maybe PubKey -> IO (Maybe PubKey)
forall (m :: * -> *) a. Monad m => a -> m a
return (PubKey -> Maybe PubKey
forall a. a -> Maybe a
Just (ByteString -> PubKey
PubKey ByteString
new_bs))
else Maybe PubKey -> IO (Maybe PubKey)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PubKey
forall a. Maybe a
Nothing
where
new_bs :: ByteString
new_bs = ByteString -> ByteString
BS.copy ByteString
pub_key
tweakMulPubKey :: PubKey -> Tweak -> Maybe PubKey
tweakMulPubKey :: PubKey -> Tweak -> Maybe PubKey
tweakMulPubKey (PubKey pub_key :: ByteString
pub_key) (Tweak t :: ByteString
t) = IO (Maybe PubKey) -> Maybe PubKey
forall a. IO a -> a
unsafePerformIO (IO (Maybe PubKey) -> Maybe PubKey)
-> IO (Maybe PubKey) -> Maybe PubKey
forall a b. (a -> b) -> a -> b
$
ByteString
-> ((Ptr PubKey64, CSize) -> IO (Maybe PubKey))
-> IO (Maybe PubKey)
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
unsafeUseByteString ByteString
new_bs (((Ptr PubKey64, CSize) -> IO (Maybe PubKey)) -> IO (Maybe PubKey))
-> ((Ptr PubKey64, CSize) -> IO (Maybe PubKey))
-> IO (Maybe PubKey)
forall a b. (a -> b) -> a -> b
$ \(pub_key_ptr :: Ptr PubKey64
pub_key_ptr, _) ->
ByteString
-> ((Ptr Tweak32, CSize) -> IO (Maybe PubKey)) -> IO (Maybe PubKey)
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
unsafeUseByteString ByteString
t (((Ptr Tweak32, CSize) -> IO (Maybe PubKey)) -> IO (Maybe PubKey))
-> ((Ptr Tweak32, CSize) -> IO (Maybe PubKey)) -> IO (Maybe PubKey)
forall a b. (a -> b) -> a -> b
$ \(tweak_ptr :: Ptr Tweak32
tweak_ptr, _) -> do
Ret
ret <- Ctx -> Ptr PubKey64 -> Ptr Tweak32 -> IO Ret
ecPubKeyTweakMul Ctx
ctx Ptr PubKey64
pub_key_ptr Ptr Tweak32
tweak_ptr
if Ret -> Bool
isSuccess Ret
ret
then Maybe PubKey -> IO (Maybe PubKey)
forall (m :: * -> *) a. Monad m => a -> m a
return (PubKey -> Maybe PubKey
forall a. a -> Maybe a
Just (ByteString -> PubKey
PubKey ByteString
new_bs))
else Maybe PubKey -> IO (Maybe PubKey)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PubKey
forall a. Maybe a
Nothing
where
new_bs :: ByteString
new_bs = ByteString -> ByteString
BS.copy ByteString
pub_key
combinePubKeys :: [PubKey] -> Maybe PubKey
combinePubKeys :: [PubKey] -> Maybe PubKey
combinePubKeys [] = Maybe PubKey
forall a. Maybe a
Nothing
combinePubKeys pubs :: [PubKey]
pubs = IO (Maybe PubKey) -> Maybe PubKey
forall a. IO a -> a
unsafePerformIO (IO (Maybe PubKey) -> Maybe PubKey)
-> IO (Maybe PubKey) -> Maybe PubKey
forall a b. (a -> b) -> a -> b
$
[Ptr PubKey64]
-> [PubKey]
-> ([Ptr PubKey64] -> IO (Maybe PubKey))
-> IO (Maybe PubKey)
forall a b. [Ptr a] -> [PubKey] -> ([Ptr a] -> IO b) -> IO b
pointers [] [PubKey]
pubs (([Ptr PubKey64] -> IO (Maybe PubKey)) -> IO (Maybe PubKey))
-> ([Ptr PubKey64] -> IO (Maybe PubKey)) -> IO (Maybe PubKey)
forall a b. (a -> b) -> a -> b
$ \ps :: [Ptr PubKey64]
ps ->
Int
-> (Ptr (Ptr PubKey64) -> IO (Maybe PubKey)) -> IO (Maybe PubKey)
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray ([Ptr PubKey64] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Ptr PubKey64]
ps) ((Ptr (Ptr PubKey64) -> IO (Maybe PubKey)) -> IO (Maybe PubKey))
-> (Ptr (Ptr PubKey64) -> IO (Maybe PubKey)) -> IO (Maybe PubKey)
forall a b. (a -> b) -> a -> b
$ \a :: Ptr (Ptr PubKey64)
a -> do
Ptr PubKey64
out <- Int -> IO (Ptr PubKey64)
forall a. Int -> IO (Ptr a)
mallocBytes 64
Ptr (Ptr PubKey64) -> [Ptr PubKey64] -> IO ()
forall a. Storable a => Ptr a -> [a] -> IO ()
pokeArray Ptr (Ptr PubKey64)
a [Ptr PubKey64]
ps
Ret
ret <- Ctx -> Ptr PubKey64 -> Ptr (Ptr PubKey64) -> Ret -> IO Ret
ecPubKeyCombine Ctx
ctx Ptr PubKey64
out Ptr (Ptr PubKey64)
a (Int -> Ret
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Ret) -> Int -> Ret
forall a b. (a -> b) -> a -> b
$ [Ptr PubKey64] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Ptr PubKey64]
ps)
if Ret -> Bool
isSuccess Ret
ret
then do
ByteString
bs <- (Ptr PubKey64, CSize) -> IO ByteString
forall a. (Ptr a, CSize) -> IO ByteString
unsafePackByteString (Ptr PubKey64
out, 64)
Maybe PubKey -> IO (Maybe PubKey)
forall (m :: * -> *) a. Monad m => a -> m a
return (PubKey -> Maybe PubKey
forall a. a -> Maybe a
Just (ByteString -> PubKey
PubKey ByteString
bs))
else do
Ptr PubKey64 -> IO ()
forall a. Ptr a -> IO ()
free Ptr PubKey64
out
Maybe PubKey -> IO (Maybe PubKey)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PubKey
forall a. Maybe a
Nothing
where
pointers :: [Ptr a] -> [PubKey] -> ([Ptr a] -> IO b) -> IO b
pointers ps :: [Ptr a]
ps [] f :: [Ptr a] -> IO b
f = [Ptr a] -> IO b
f [Ptr a]
ps
pointers ps :: [Ptr a]
ps (PubKey pub_key :: ByteString
pub_key : pub_keys :: [PubKey]
pub_keys) f :: [Ptr a] -> IO b
f =
ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
unsafeUseByteString ByteString
pub_key (((Ptr a, CSize) -> IO b) -> IO b)
-> ((Ptr a, CSize) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \(p :: Ptr a
p, _) ->
[Ptr a] -> [PubKey] -> ([Ptr a] -> IO b) -> IO b
pointers (Ptr a
p Ptr a -> [Ptr a] -> [Ptr a]
forall a. a -> [a] -> [a]
: [Ptr a]
ps) [PubKey]
pub_keys [Ptr a] -> IO b
f
tweakNegate :: Tweak -> Maybe Tweak
tweakNegate :: Tweak -> Maybe Tweak
tweakNegate (Tweak t :: ByteString
t) = IO (Maybe Tweak) -> Maybe Tweak
forall a. IO a -> a
unsafePerformIO (IO (Maybe Tweak) -> Maybe Tweak)
-> IO (Maybe Tweak) -> Maybe Tweak
forall a b. (a -> b) -> a -> b
$
ByteString
-> ((Ptr Tweak32, CSize) -> IO (Maybe Tweak)) -> IO (Maybe Tweak)
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
unsafeUseByteString ByteString
new (((Ptr Tweak32, CSize) -> IO (Maybe Tweak)) -> IO (Maybe Tweak))
-> ((Ptr Tweak32, CSize) -> IO (Maybe Tweak)) -> IO (Maybe Tweak)
forall a b. (a -> b) -> a -> b
$ \(out :: Ptr Tweak32
out, _) -> do
Ret
ret <- Ctx -> Ptr Tweak32 -> IO Ret
ecTweakNegate Ctx
ctx Ptr Tweak32
out
if Ret -> Bool
isSuccess Ret
ret
then Maybe Tweak -> IO (Maybe Tweak)
forall (m :: * -> *) a. Monad m => a -> m a
return (Tweak -> Maybe Tweak
forall a. a -> Maybe a
Just (ByteString -> Tweak
Tweak ByteString
new))
else Maybe Tweak -> IO (Maybe Tweak)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Tweak
forall a. Maybe a
Nothing
where
new :: ByteString
new = ByteString -> ByteString
BS.copy ByteString
t
instance Arbitrary Msg where
arbitrary :: Gen Msg
arbitrary = Gen Msg
gen_msg
where
valid_bs :: Gen (Maybe Msg)
valid_bs = Gen (Maybe Msg)
bs_gen Gen (Maybe Msg) -> (Maybe Msg -> Bool) -> Gen (Maybe Msg)
forall a. Gen a -> (a -> Bool) -> Gen a
`suchThat` Maybe Msg -> Bool
forall a. Maybe a -> Bool
isJust
bs_gen :: Gen (Maybe Msg)
bs_gen = ByteString -> Maybe Msg
msg (ByteString -> Maybe Msg)
-> ([Word8] -> ByteString) -> [Word8] -> Maybe Msg
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Word8] -> ByteString
BS.pack ([Word8] -> Maybe Msg) -> Gen [Word8] -> Gen (Maybe Msg)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Gen Word8 -> Gen [Word8]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM 32 Gen Word8
forall a. (Bounded a, Random a) => Gen a
arbitraryBoundedRandom
gen_msg :: Gen Msg
gen_msg = Maybe Msg -> Msg
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe Msg -> Msg) -> Gen (Maybe Msg) -> Gen Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (Maybe Msg)
valid_bs
instance Arbitrary SecKey where
arbitrary :: Gen SecKey
arbitrary = Gen SecKey
gen_key where
valid_bs :: Gen (Maybe SecKey)
valid_bs = Gen (Maybe SecKey)
bs_gen Gen (Maybe SecKey) -> (Maybe SecKey -> Bool) -> Gen (Maybe SecKey)
forall a. Gen a -> (a -> Bool) -> Gen a
`suchThat` Maybe SecKey -> Bool
forall a. Maybe a -> Bool
isJust
bs_gen :: Gen (Maybe SecKey)
bs_gen = ByteString -> Maybe SecKey
secKey (ByteString -> Maybe SecKey)
-> ([Word8] -> ByteString) -> [Word8] -> Maybe SecKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Word8] -> ByteString
BS.pack ([Word8] -> Maybe SecKey) -> Gen [Word8] -> Gen (Maybe SecKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Gen Word8 -> Gen [Word8]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM 32 Gen Word8
forall a. (Bounded a, Random a) => Gen a
arbitraryBoundedRandom
gen_key :: Gen SecKey
gen_key = Maybe SecKey -> SecKey
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe SecKey -> SecKey) -> Gen (Maybe SecKey) -> Gen SecKey
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (Maybe SecKey)
valid_bs
instance Arbitrary PubKey where
arbitrary :: Gen PubKey
arbitrary = SecKey -> PubKey
derivePubKey (SecKey -> PubKey) -> Gen SecKey -> Gen PubKey
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen SecKey
forall a. Arbitrary a => Gen a
arbitrary