-- | Implementation to be used when compiled with GHC
module BIP32.GHC
  ( Prv
  , prv
  , unPrv
  , prvToPub
  , addPrvTweak

  , Pub
  , pub
  , unPub
  , addPubTweak

  , Tweak
  , tweak

  , hmacSHA512
  , ripemd160
  , sha256
  ) where

import Control.Monad
import qualified Crypto.Hash as Hash
import qualified Crypto.MAC.HMAC as HMAC
import qualified Crypto.Secp256k1 as K
import qualified Data.ByteArray as BA
import qualified Data.ByteString as B

--------------------------------------------------------------------------------

-- | Private key.
--
-- Construct with 'prv'.
newtype Prv = Prv K.SecKey
  deriving (Eq, Show)

-- | Obtain the 32 raw bytes inside a 'Prv'. See 'prv'.
unPrv :: Prv -> B.ByteString
{-# INLINE unPrv #-}
unPrv (Prv x) = K.getSecKey x

-- | Construct a 'Prv' key from its raw bytes.
--
-- * 32 bytes containing \(ser_{256}(k)\).
--
-- See Bitcoin's [BIP-0032](https://github.com/bitcoin/bips/blob/master/bip-0032.mediawiki)
-- for details.
--
-- 'Nothing' if something is not satisfied.
prv :: B.ByteString -> Maybe Prv
{-# INLINE prv #-}
prv x = Prv <$> K.secKey x

-- | Obtain the 'Pub' key for 'Prv'.
prvToPub :: Prv -> Pub
{-# INLINE prvToPub #-}
prvToPub (Prv x) = Pub (K.derivePubKey x)

-- | Tweak a 'Prv'ate key by adding 'Tweak' times the generator to it.
addPrvTweak :: Prv -> Tweak -> Maybe Prv
{-# INLINE addPrvTweak #-}
addPrvTweak (Prv p) (Tweak t) = Prv <$> K.tweakAddSecKey p t

--------------------------------------------------------------------------------

-- | Public key.
--
-- Construct with 'pub'.
newtype Pub = Pub K.PubKey
  deriving (Eq, Show)

-- | Obtain the 33 raw bytes inside a 'Pub'. See 'pub'.
--
-- Corresponds to BIP-0032's \(ser_{P}(P)\).
unPub :: Pub -> B.ByteString
{-# INLINE unPub #-}
unPub (Pub x) = K.exportPubKey True x

-- | Construct a 'Pub' key from its raw bytes.
--
-- * 33 bytes in total, containing \(ser_{P}(P)\).
--
-- * The leftmost byte is either @0x02@ or @0x03@, depending on the parity
-- of the omitted @y@ coordinate.
--
-- * The remaining 32 bytes are \(ser_{256}(x)\).
--
-- See Bitcoin's [BIP-0032](https://github.com/bitcoin/bips/blob/master/bip-0032.mediawiki)
-- for details.
--
-- 'Nothing' if something is not satisfied.
pub :: B.ByteString -> Maybe Pub
{-# INLINE pub #-}
pub x = do
  guard (B.length x == 33)
  Pub <$> K.importPubKey x

-- | Tweak a 'Pub'lic key by adding 'Tweak' times the generator to it.
addPubTweak :: Pub -> Tweak -> Maybe Pub
{-# INLINE addPubTweak #-}
addPubTweak (Pub p) (Tweak t) = Pub <$> K.tweakAddPubKey p t

--------------------------------------------------------------------------------

newtype Tweak = Tweak K.Tweak

-- | Convert a 32-Byte 'B.ByteString' to a 'Tweak'.
tweak :: B.ByteString -> Maybe Tweak
{-# INLINE tweak #-}
tweak x = Tweak <$> K.tweak x

--------------------------------------------------------------------------------

hmacSHA512
  :: B.ByteString  -- ^ Key.
  -> B.ByteString  -- ^ Data to hash.
  -> B.ByteString  -- ^ 64-byte long digest.
{-# INLINE hmacSHA512 #-}
hmacSHA512 k d = BA.convert (HMAC.hmac k d :: HMAC.HMAC Hash.SHA512)

ripemd160
  :: B.ByteString  -- ^ Data to hash.
  -> B.ByteString  -- ^ 20-byte long digest.
{-# INLINE ripemd160 #-}
ripemd160 d = BA.convert (Hash.hash d :: Hash.Digest Hash.RIPEMD160)

sha256
  :: B.ByteString  -- ^ Data to hash.
  -> B.ByteString  -- ^ 32-byte long digest.
{-# INLINE sha256 #-}
sha256 d = BA.convert (Hash.hash d :: Hash.Digest Hash.SHA256)