module Botan.Low.PubKey.ECDSA where

import Botan.Bindings.PubKey
import Botan.Bindings.PubKey.ECDSA

import Botan.Low.MPI
import Botan.Low.Prelude
import Botan.Low.PubKey

privKeyLoadECDSA
    :: MP           -- ^ __scalar__
    -> ByteString   -- ^ __curve_name__
    -> IO PrivKey   -- ^ __key__
privKeyLoadECDSA :: MP -> ByteString -> IO PrivKey
privKeyLoadECDSA = (Ptr BotanPrivKey
 -> BotanMP -> ConstPtr CChar -> IO BotanErrorCode)
-> MP -> ByteString -> IO PrivKey
mkPrivKeyLoad1_name Ptr BotanPrivKey -> BotanMP -> ConstPtr CChar -> IO BotanErrorCode
botan_privkey_load_ecdsa

pubKeyLoadECDSA
    :: MP           -- ^ __public_x__
    -> MP           -- ^ __public_y__
    -> ByteString   -- ^ __curve_name__
    -> IO PubKey    -- ^ __key__
pubKeyLoadECDSA :: MP -> MP -> ByteString -> IO PubKey
pubKeyLoadECDSA = (Ptr BotanPubKey
 -> BotanMP -> BotanMP -> ConstPtr CChar -> IO BotanErrorCode)
-> MP -> MP -> ByteString -> IO PubKey
mkPubKeyLoad2_name Ptr BotanPubKey
-> BotanMP -> BotanMP -> ConstPtr CChar -> IO BotanErrorCode
botan_pubkey_load_ecdsa