{-# LANGUAGE DataKinds #-}
{-# 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,
) where
import Control.DeepSeq (NFData)
import Control.Monad (replicateM, unless, (<=<))
import qualified Crypto.Secp256k1.Prim as Prim
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 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 Int
64
instance Serialize Msg where
put :: Putter Msg
put (Msg 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 Int
32
instance Serialize Sig where
put :: Putter Sig
put (Sig 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 Int
64
instance Serialize SecKey where
put :: Putter SecKey
put (SecKey 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 Int
32
instance Serialize Tweak where
put :: Putter Tweak
put (Tweak 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 Int
32
instance Serialize CompactSig where
put :: Putter CompactSig
put (CompactSig 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 Int
64
decodeHex :: ConvertibleStrings a ByteString => a -> Maybe ByteString
decodeHex :: forall a. ConvertibleStrings a ByteString => a -> Maybe ByteString
decodeHex 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 ByteString
bs -> ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
bs
Left Text
_ -> Maybe ByteString
forall a. Maybe a
Nothing
instance Read PubKey where
readPrec :: ReadPrec PubKey
readPrec = do
String 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
Int
i hashWithSalt :: Int -> PubKey -> Int
`hashWithSalt` 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 String
"Could not decode public key from hex string"
instance Show PubKey where
showsPrec :: Int -> PubKey -> ShowS
showsPrec Int
_ = 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 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
Int
i hashWithSalt :: Int -> Msg -> Int
`hashWithSalt` 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 String
"Could not decode message from hex string"
instance Show Msg where
showsPrec :: Int -> Msg -> ShowS
showsPrec Int
_ = 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 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 String
"Could not decode signature from hex string"
instance Hashable Sig where
Int
i hashWithSalt :: Int -> Sig -> Int
`hashWithSalt` 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 Int
_ = 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 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
Int
i hashWithSalt :: Int -> SecKey -> Int
`hashWithSalt` 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 String
"Colud not decode secret key from hex string"
instance Show SecKey where
showsPrec :: Int -> SecKey -> ShowS
showsPrec Int
_ = 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
Int
i hashWithSalt :: Int -> Tweak -> Int
`hashWithSalt` 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 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 String
"Could not decode tweak from hex string"
instance Show Tweak where
showsPrec :: Int -> Tweak -> ShowS
showsPrec Int
_ = 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 ByteString
bs
| ByteString -> Int
BS.length ByteString
bs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
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 ByteString
bs
| ByteString -> Int
BS.length ByteString
bs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
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 ByteString
bs
| ByteString -> Int
BS.length ByteString
bs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
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 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
Prim.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
$ \(Ptr Sig64
sig_in, CSize
_) -> do
Ptr Sig64
sig_out <- Int -> IO (Ptr Sig64)
forall a. Int -> IO (Ptr a)
mallocBytes Int
64
CInt
ret <- Ctx -> Ptr Sig64 -> Ptr Sig64 -> IO CInt
Prim.ecdsaSignatureNormalize Ctx
Prim.ctx Ptr Sig64
sig_out Ptr Sig64
sig_in
if CInt -> Bool
Prim.isSuccess CInt
ret
then do
ByteString
bs <- (Ptr Sig64, CSize) -> IO ByteString
forall a. (Ptr a, CSize) -> IO ByteString
Prim.unsafePackByteString (Ptr Sig64
sig_out, CSize
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 ByteString
bs
| ByteString -> Int
BS.length ByteString
bs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
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 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 (Bytes Any), CSize) -> IO (Maybe PubKey))
-> IO (Maybe PubKey)
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
Prim.unsafeUseByteString ByteString
bs (((Ptr (Bytes Any), CSize) -> IO (Maybe PubKey))
-> IO (Maybe PubKey))
-> ((Ptr (Bytes Any), CSize) -> IO (Maybe PubKey))
-> IO (Maybe PubKey)
forall a b. (a -> b) -> a -> b
$ \(Ptr (Bytes Any)
input, CSize
len) -> do
Ptr Pubkey64
pub_key <- Int -> IO (Ptr Pubkey64)
forall a. Int -> IO (Ptr a)
mallocBytes Int
64
CInt
ret <- Ctx -> Ptr Pubkey64 -> Ptr (Bytes Any) -> CSize -> IO CInt
forall (n :: Nat).
Ctx -> Ptr Pubkey64 -> Ptr (Bytes n) -> CSize -> IO CInt
Prim.ecPubkeyParse Ctx
Prim.ctx Ptr Pubkey64
pub_key Ptr (Bytes Any)
input CSize
len
if CInt -> Bool
Prim.isSuccess CInt
ret
then do
ByteString
out <- (Ptr Pubkey64, CSize) -> IO ByteString
forall a. (Ptr a, CSize) -> IO ByteString
Prim.unsafePackByteString (Ptr Pubkey64
pub_key, CSize
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 Bool
compress (PubKey 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
Prim.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
$ \(Ptr Pubkey64
in_ptr, CSize
_) ->
(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
$ \Ptr CSize
len_ptr ->
Int -> (Ptr (Bytes Any) -> IO ByteString) -> IO ByteString
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
len ((Ptr (Bytes Any) -> IO ByteString) -> IO ByteString)
-> (Ptr (Bytes Any) -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr (Bytes Any)
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
CInt
ret <- Ctx
-> Ptr (Bytes Any)
-> Ptr CSize
-> Ptr Pubkey64
-> SerFlags
-> IO CInt
forall (n :: Nat).
Ctx
-> Ptr (Bytes n)
-> Ptr CSize
-> Ptr Pubkey64
-> SerFlags
-> IO CInt
Prim.ecPubKeySerialize Ctx
Prim.ctx Ptr (Bytes Any)
out_ptr Ptr CSize
len_ptr Ptr Pubkey64
in_ptr SerFlags
flags
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (CInt -> Bool
Prim.isSuccess CInt
ret) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO ()
forall a. HasCallStack => String -> a
error String
"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 (Bytes Any), CSize) -> IO ByteString
forall a. (Ptr a, CSize) -> IO ByteString
Prim.packByteString (Ptr (Bytes Any)
out_ptr, CSize
final_len)
where
len :: Int
len = if Bool
compress then Int
33 else Int
65
flags :: SerFlags
flags = if Bool
compress then SerFlags
Prim.compressed else SerFlags
Prim.uncompressed
exportCompactSig :: Sig -> CompactSig
exportCompactSig :: Sig -> CompactSig
exportCompactSig (Sig 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
Prim.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
$ \(Ptr Sig64
sig_ptr, CSize
_) -> do
Ptr Compact64
out_ptr <- Int -> IO (Ptr Compact64)
forall a. Int -> IO (Ptr a)
mallocBytes Int
64
CInt
ret <- Ctx -> Ptr Compact64 -> Ptr Sig64 -> IO CInt
Prim.ecdsaSignatureSerializeCompact Ctx
Prim.ctx Ptr Compact64
out_ptr Ptr Sig64
sig_ptr
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (CInt -> Bool
Prim.isSuccess CInt
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 String
"Could not obtain compact signature"
ByteString
out_bs <- (Ptr Compact64, CSize) -> IO ByteString
forall a. (Ptr a, CSize) -> IO ByteString
Prim.unsafePackByteString (Ptr Compact64
out_ptr, CSize
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 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
Prim.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
$ \(Ptr Compact64
compact_ptr, CSize
_) -> do
Ptr Sig64
out_sig <- Int -> IO (Ptr Sig64)
forall a. Int -> IO (Ptr a)
mallocBytes Int
64
CInt
ret <- Ctx -> Ptr Sig64 -> Ptr Compact64 -> IO CInt
Prim.ecdsaSignatureParseCompact Ctx
Prim.ctx Ptr Sig64
out_sig Ptr Compact64
compact_ptr
if CInt -> Bool
Prim.isSuccess CInt
ret
then do
ByteString
out_bs <- (Ptr Sig64, CSize) -> IO ByteString
forall a. (Ptr a, CSize) -> IO ByteString
Prim.unsafePackByteString (Ptr Sig64
out_sig, CSize
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 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 (Bytes Any), CSize) -> IO (Maybe Sig)) -> IO (Maybe Sig)
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
Prim.unsafeUseByteString ByteString
bs (((Ptr (Bytes Any), CSize) -> IO (Maybe Sig)) -> IO (Maybe Sig))
-> ((Ptr (Bytes Any), CSize) -> IO (Maybe Sig)) -> IO (Maybe Sig)
forall a b. (a -> b) -> a -> b
$ \(Ptr (Bytes Any)
in_ptr, CSize
in_len) -> do
Ptr Sig64
out_sig <- Int -> IO (Ptr Sig64)
forall a. Int -> IO (Ptr a)
mallocBytes Int
64
CInt
ret <- Ctx -> Ptr Sig64 -> Ptr (Bytes Any) -> CSize -> IO CInt
forall (n :: Nat).
Ctx -> Ptr Sig64 -> Ptr (Bytes n) -> CSize -> IO CInt
Prim.ecdsaSignatureParseDer Ctx
Prim.ctx Ptr Sig64
out_sig Ptr (Bytes Any)
in_ptr CSize
in_len
if CInt -> Bool
Prim.isSuccess CInt
ret
then do
ByteString
out_bs <- (Ptr Sig64, CSize) -> IO ByteString
forall a. (Ptr a, CSize) -> IO ByteString
Prim.unsafePackByteString (Ptr Sig64
out_sig, CSize
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 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
Prim.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
$ \(Ptr Sig64
in_ptr, CSize
_) ->
(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
$ \Ptr CSize
out_len ->
Int -> (Ptr (Bytes Any) -> IO ByteString) -> IO ByteString
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
72 ((Ptr (Bytes Any) -> IO ByteString) -> IO ByteString)
-> (Ptr (Bytes Any) -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr (Bytes Any)
out_ptr -> do
Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr CSize
out_len CSize
72
CInt
ret <- Ctx -> Ptr (Bytes Any) -> Ptr CSize -> Ptr Sig64 -> IO CInt
forall (n :: Nat).
Ctx -> Ptr (Bytes n) -> Ptr CSize -> Ptr Sig64 -> IO CInt
Prim.ecdsaSignatureSerializeDer Ctx
Prim.ctx Ptr (Bytes Any)
out_ptr Ptr CSize
out_len Ptr Sig64
in_ptr
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (CInt -> Bool
Prim.isSuccess CInt
ret) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO ()
forall a. HasCallStack => String -> a
error String
"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 (Bytes Any), CSize) -> IO ByteString
forall a. (Ptr a, CSize) -> IO ByteString
Prim.packByteString (Ptr (Bytes Any)
out_ptr, CSize
final_len)
verifySig :: PubKey -> Sig -> Msg -> Bool
verifySig :: PubKey -> Sig -> Msg -> Bool
verifySig (PubKey ByteString
pub_key) (Sig ByteString
sig) (Msg 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
Prim.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
$ \(Ptr Pubkey64
pub_key_ptr, CSize
_) ->
ByteString -> ((Ptr Sig64, CSize) -> IO Bool) -> IO Bool
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
Prim.unsafeUseByteString ByteString
sig (((Ptr Sig64, CSize) -> IO Bool) -> IO Bool)
-> ((Ptr Sig64, CSize) -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \(Ptr Sig64
sig_ptr, CSize
_) ->
ByteString -> ((Ptr Msg32, CSize) -> IO Bool) -> IO Bool
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
Prim.unsafeUseByteString ByteString
m (((Ptr Msg32, CSize) -> IO Bool) -> IO Bool)
-> ((Ptr Msg32, CSize) -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \(Ptr Msg32
msg_ptr, CSize
_) ->
CInt -> Bool
Prim.isSuccess (CInt -> Bool) -> IO CInt -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ctx -> Ptr Sig64 -> Ptr Msg32 -> Ptr Pubkey64 -> IO CInt
Prim.ecdsaVerify Ctx
Prim.ctx Ptr Sig64
sig_ptr Ptr Msg32
msg_ptr Ptr Pubkey64
pub_key_ptr
signMsg :: SecKey -> Msg -> Sig
signMsg :: SecKey -> Msg -> Sig
signMsg (SecKey ByteString
sec_key) (Msg 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
Prim.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
$ \(Ptr Seckey32
sec_key_ptr, CSize
_) ->
ByteString -> ((Ptr Msg32, CSize) -> IO Sig) -> IO Sig
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
Prim.unsafeUseByteString ByteString
m (((Ptr Msg32, CSize) -> IO Sig) -> IO Sig)
-> ((Ptr Msg32, CSize) -> IO Sig) -> IO Sig
forall a b. (a -> b) -> a -> b
$ \(Ptr Msg32
msg_ptr, CSize
_) -> do
Ptr Sig64
sig_ptr <- Int -> IO (Ptr Sig64)
forall a. Int -> IO (Ptr a)
mallocBytes Int
64
CInt
ret <- Ctx
-> Ptr Sig64
-> Ptr Msg32
-> Ptr Seckey32
-> FunPtr (NonceFun Any)
-> Ptr Any
-> IO CInt
forall a.
Ctx
-> Ptr Sig64
-> Ptr Msg32
-> Ptr Seckey32
-> FunPtr (NonceFun a)
-> Ptr a
-> IO CInt
Prim.ecdsaSign Ctx
Prim.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 (CInt -> Bool
Prim.isSuccess CInt
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 String
"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
Prim.unsafePackByteString (Ptr Sig64
sig_ptr, CSize
64)
derivePubKey :: SecKey -> PubKey
derivePubKey :: SecKey -> PubKey
derivePubKey (SecKey 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
Prim.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
$ \(Ptr Seckey32
sec_key_ptr, CSize
_) -> do
Ptr Pubkey64
pub_key_ptr <- Int -> IO (Ptr Pubkey64)
forall a. Int -> IO (Ptr a)
mallocBytes Int
64
CInt
ret <- Ctx -> Ptr Pubkey64 -> Ptr Seckey32 -> IO CInt
Prim.ecPubKeyCreate Ctx
Prim.ctx Ptr Pubkey64
pub_key_ptr Ptr Seckey32
sec_key_ptr
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (CInt -> Bool
Prim.isSuccess CInt
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 String
"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
Prim.unsafePackByteString (Ptr Pubkey64
pub_key_ptr, CSize
64)
tweakAddSecKey :: SecKey -> Tweak -> Maybe SecKey
tweakAddSecKey :: SecKey -> Tweak -> Maybe SecKey
tweakAddSecKey (SecKey ByteString
sec_key) (Tweak 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
Prim.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
$ \(Ptr Seckey32
sec_key_ptr, CSize
_) ->
ByteString
-> ((Ptr Tweak32, CSize) -> IO (Maybe SecKey)) -> IO (Maybe SecKey)
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
Prim.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
$ \(Ptr Tweak32
tweak_ptr, CSize
_) -> do
CInt
ret <- Ctx -> Ptr Seckey32 -> Ptr Tweak32 -> IO CInt
Prim.ecSeckeyTweakAdd Ctx
Prim.ctx Ptr Seckey32
sec_key_ptr Ptr Tweak32
tweak_ptr
if CInt -> Bool
Prim.isSuccess CInt
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 ByteString
sec_key) (Tweak 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
Prim.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
$ \(Ptr Seckey32
sec_key_ptr, CSize
_) ->
ByteString
-> ((Ptr Tweak32, CSize) -> IO (Maybe SecKey)) -> IO (Maybe SecKey)
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
Prim.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
$ \(Ptr Tweak32
tweak_ptr, CSize
_) -> do
CInt
ret <- Ctx -> Ptr Seckey32 -> Ptr Tweak32 -> IO CInt
Prim.ecSeckeyTweakMul Ctx
Prim.ctx Ptr Seckey32
sec_key_ptr Ptr Tweak32
tweak_ptr
if CInt -> Bool
Prim.isSuccess CInt
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 ByteString
pub_key) (Tweak 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
Prim.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
$ \(Ptr Pubkey64
pub_key_ptr, CSize
_) ->
ByteString
-> ((Ptr Tweak32, CSize) -> IO (Maybe PubKey)) -> IO (Maybe PubKey)
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
Prim.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
$ \(Ptr Tweak32
tweak_ptr, CSize
_) -> do
CInt
ret <- Ctx -> Ptr Pubkey64 -> Ptr Tweak32 -> IO CInt
Prim.ecPubKeyTweakAdd Ctx
Prim.ctx Ptr Pubkey64
pub_key_ptr Ptr Tweak32
tweak_ptr
if CInt -> Bool
Prim.isSuccess CInt
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 ByteString
pub_key) (Tweak 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
Prim.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
$ \(Ptr Pubkey64
pub_key_ptr, CSize
_) ->
ByteString
-> ((Ptr Tweak32, CSize) -> IO (Maybe PubKey)) -> IO (Maybe PubKey)
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
Prim.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
$ \(Ptr Tweak32
tweak_ptr, CSize
_) -> do
CInt
ret <- Ctx -> Ptr Pubkey64 -> Ptr Tweak32 -> IO CInt
Prim.ecPubKeyTweakMul Ctx
Prim.ctx Ptr Pubkey64
pub_key_ptr Ptr Tweak32
tweak_ptr
if CInt -> Bool
Prim.isSuccess CInt
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 [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
$ \[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
$ \Ptr (Ptr Pubkey64)
a -> do
Ptr Pubkey64
out <- Int -> IO (Ptr Pubkey64)
forall a. Int -> IO (Ptr a)
mallocBytes Int
64
Ptr (Ptr Pubkey64) -> [Ptr Pubkey64] -> IO ()
forall a. Storable a => Ptr a -> [a] -> IO ()
pokeArray Ptr (Ptr Pubkey64)
a [Ptr Pubkey64]
ps
CInt
ret <- Ctx -> Ptr Pubkey64 -> Ptr (Ptr Pubkey64) -> CInt -> IO CInt
Prim.ecPubKeyCombine Ctx
Prim.ctx Ptr Pubkey64
out Ptr (Ptr Pubkey64)
a (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ [Ptr Pubkey64] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Ptr Pubkey64]
ps)
if CInt -> Bool
Prim.isSuccess CInt
ret
then do
ByteString
bs <- (Ptr Pubkey64, CSize) -> IO ByteString
forall a. (Ptr a, CSize) -> IO ByteString
Prim.unsafePackByteString (Ptr Pubkey64
out, CSize
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 [Ptr a]
ps [] [Ptr a] -> IO b
f = [Ptr a] -> IO b
f [Ptr a]
ps
pointers [Ptr a]
ps (PubKey ByteString
pub_key : [PubKey]
pub_keys) [Ptr a] -> IO b
f =
ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b
Prim.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
$ \(Ptr a
p, CSize
_) ->
[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
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 Int
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 Int
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