module Hydra.Cardano.Api.Hash where
import Hydra.Cardano.Api.Prelude
import Cardano.Ledger.Hashes (unsafeMakeSafeHash)
import Cardano.Ledger.Keys qualified as Ledger
import Cardano.Ledger.Plutus.TxInfo (transKeyHash)
import Data.ByteString qualified as BS
import PlutusLedgerApi.V3 qualified as Plutus
toPlutusKeyHash :: Hash PaymentKey -> Plutus.PubKeyHash
toPlutusKeyHash :: Hash PaymentKey -> PubKeyHash
toPlutusKeyHash (PaymentKeyHash KeyHash 'Payment
vkh) = KeyHash 'Payment -> PubKeyHash
forall (d :: KeyRole). KeyHash d -> PubKeyHash
transKeyHash KeyHash 'Payment
vkh
toLedgerKeyHash :: Hash PaymentKey -> Ledger.KeyHash 'Ledger.Witness
toLedgerKeyHash :: Hash PaymentKey -> KeyHash 'Witness
toLedgerKeyHash (PaymentKeyHash (Ledger.KeyHash Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh)) =
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Witness
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Ledger.KeyHash Hash ADDRHASH (VerKeyDSIGN DSIGN)
vkh
unsafePaymentKeyHashFromBytes ::
HasCallStack =>
ByteString ->
Hash PaymentKey
unsafePaymentKeyHashFromBytes :: HasCallStack => ByteString -> Hash PaymentKey
unsafePaymentKeyHashFromBytes ByteString
bytes
| ByteString -> Int
BS.length ByteString
bytes Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
28 =
[Char] -> Hash PaymentKey
forall a. HasCallStack => [Char] -> a
error ([Char] -> Hash PaymentKey) -> [Char] -> Hash PaymentKey
forall a b. (a -> b) -> a -> b
$ [Char]
"unsafePaymentKeyHashFromBytes: pre-condition failed: " [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> Int -> [Char]
forall a. Show a => a -> [Char]
show (ByteString -> Int
BS.length ByteString
bytes) [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
" bytes."
| Bool
otherwise =
KeyHash 'Payment -> Hash PaymentKey
PaymentKeyHash (KeyHash 'Payment -> Hash PaymentKey)
-> KeyHash 'Payment -> Hash PaymentKey
forall a b. (a -> b) -> a -> b
$ Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Payment
forall (r :: KeyRole).
Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash r
Ledger.KeyHash (Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Payment)
-> Hash ADDRHASH (VerKeyDSIGN DSIGN) -> KeyHash 'Payment
forall a b. (a -> b) -> a -> b
$ ByteString -> Hash ADDRHASH (VerKeyDSIGN DSIGN)
forall hash a.
(HasCallStack, HashAlgorithm hash) =>
ByteString -> Hash hash a
unsafeHashFromBytes ByteString
bytes
unsafeScriptDataHashFromBytes ::
HasCallStack =>
ByteString ->
Hash ScriptData
unsafeScriptDataHashFromBytes :: HasCallStack => ByteString -> Hash ScriptData
unsafeScriptDataHashFromBytes ByteString
bytes
| ByteString -> Int
BS.length ByteString
bytes Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
32 =
[Char] -> Hash ScriptData
forall a. HasCallStack => [Char] -> a
error ([Char] -> Hash ScriptData) -> [Char] -> Hash ScriptData
forall a b. (a -> b) -> a -> b
$ [Char]
"unsafeScriptDataHashFromBytes: pre-condition failed: " [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> Int -> [Char]
forall a. Show a => a -> [Char]
show (ByteString -> Int
BS.length ByteString
bytes) [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
" bytes."
| Bool
otherwise =
DataHash -> Hash ScriptData
ScriptDataHash
(DataHash -> Hash ScriptData)
-> (Hash HASH EraIndependentData -> DataHash)
-> Hash HASH EraIndependentData
-> Hash ScriptData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash HASH EraIndependentData -> DataHash
forall i. Hash HASH i -> SafeHash i
unsafeMakeSafeHash
(Hash HASH EraIndependentData -> Hash ScriptData)
-> Hash HASH EraIndependentData -> Hash ScriptData
forall a b. (a -> b) -> a -> b
$ ByteString -> Hash HASH EraIndependentData
forall hash a.
(HasCallStack, HashAlgorithm hash) =>
ByteString -> Hash hash a
unsafeHashFromBytes ByteString
bytes
unsafeCastHash ::
(SerialiseAsCBOR (Hash a), SerialiseAsCBOR (Hash b), HasCallStack) =>
Hash a ->
Hash b
unsafeCastHash :: forall a b.
(SerialiseAsCBOR (Hash a), SerialiseAsCBOR (Hash b),
HasCallStack) =>
Hash a -> Hash b
unsafeCastHash Hash a
a =
(DecoderError -> Hash b)
-> (Hash b -> Hash b) -> Either DecoderError (Hash b) -> Hash b
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
(\DecoderError
e -> [Char] -> Hash b
forall a. HasCallStack => [Char] -> a
error ([Char] -> Hash b) -> [Char] -> Hash b
forall a b. (a -> b) -> a -> b
$ [Char]
"unsafeCastHash: incompatible hash: " [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> DecoderError -> [Char]
forall a. Show a => a -> [Char]
show DecoderError
e)
Hash b -> Hash b
forall a. a -> a
id
(AsType (Hash b) -> ByteString -> Either DecoderError (Hash b)
forall a.
SerialiseAsCBOR a =>
AsType a -> ByteString -> Either DecoderError a
deserialiseFromCBOR (Proxy (Hash b) -> AsType (Hash b)
forall t. HasTypeProxy t => Proxy t -> AsType t
proxyToAsType Proxy (Hash b)
forall {k} (t :: k). Proxy t
Proxy) (Hash a -> ByteString
forall a. SerialiseAsCBOR a => a -> ByteString
serialiseToCBOR Hash a
a))