{-# OPTIONS_GHC -Wno-orphans #-}

module Hydra.Cardano.Api.PolicyId where

import Hydra.Cardano.Api.Prelude

import Cardano.Ledger.Alonzo.Plutus.TxInfo qualified as Ledger
import Cardano.Ledger.Hashes qualified as Ledger
import Cardano.Ledger.Mary.Value qualified as Ledger
import Hydra.Cardano.Api.ScriptHash ()
import PlutusLedgerApi.V2 (CurrencySymbol, fromBuiltin, unCurrencySymbol)

-- * Orphans

instance Arbitrary PolicyId where
  arbitrary :: Gen PolicyId
arbitrary = ScriptHash -> PolicyId
PolicyId (ScriptHash -> PolicyId) -> Gen ScriptHash -> Gen PolicyId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen ScriptHash
forall a. Arbitrary a => Gen a
arbitrary

-- * Type conversions

toLedgerScriptHash :: PolicyId -> Ledger.ScriptHash StandardCrypto
toLedgerScriptHash :: PolicyId -> ScriptHash StandardCrypto
toLedgerScriptHash (PolicyId ScriptHash
scriptHash) = ScriptHash -> ScriptHash StandardCrypto
toShelleyScriptHash ScriptHash
scriptHash

-- | Convert Cardano api 'PolicyId' to Cardano ledger `PolicyID`.
toLedgerPolicyID :: PolicyId -> Ledger.PolicyID StandardCrypto
toLedgerPolicyID :: PolicyId -> PolicyID StandardCrypto
toLedgerPolicyID (PolicyId ScriptHash
sh) = ScriptHash StandardCrypto -> PolicyID StandardCrypto
forall c. ScriptHash c -> PolicyID c
Ledger.PolicyID (ScriptHash -> ScriptHash StandardCrypto
toShelleyScriptHash ScriptHash
sh)

-- | Convert Cardano api 'PolicyId' to Plutus `CurrencySymbol`.
toPlutusCurrencySymbol :: PolicyId -> CurrencySymbol
toPlutusCurrencySymbol :: PolicyId -> CurrencySymbol
toPlutusCurrencySymbol = PolicyID StandardCrypto -> CurrencySymbol
forall c. PolicyID c -> CurrencySymbol
Ledger.transPolicyID (PolicyID StandardCrypto -> CurrencySymbol)
-> (PolicyId -> PolicyID StandardCrypto)
-> PolicyId
-> CurrencySymbol
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PolicyId -> PolicyID StandardCrypto
toLedgerPolicyID

-- | Convert a plutus 'CurrencySymbol' into a cardano-api 'PolicyId'.
fromPlutusCurrencySymbol :: MonadFail m => CurrencySymbol -> m PolicyId
fromPlutusCurrencySymbol :: forall (m :: * -> *). MonadFail m => CurrencySymbol -> m PolicyId
fromPlutusCurrencySymbol CurrencySymbol
cs =
  case AsType PolicyId
-> ByteString -> Either SerialiseAsRawBytesError PolicyId
forall a.
SerialiseAsRawBytes a =>
AsType a -> ByteString -> Either SerialiseAsRawBytesError a
deserialiseFromRawBytes AsType PolicyId
AsPolicyId ByteString
bytes of
    Left SerialiseAsRawBytesError
err -> String -> m PolicyId
forall a. String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (SerialiseAsRawBytesError -> String
forall a. Show a => a -> String
show SerialiseAsRawBytesError
err)
    Right PolicyId
pid -> PolicyId -> m PolicyId
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure PolicyId
pid
 where
  bytes :: ByteString
bytes = BuiltinByteString -> ByteString
forall arep a. FromBuiltin arep a => arep -> a
fromBuiltin (BuiltinByteString -> ByteString)
-> BuiltinByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ CurrencySymbol -> BuiltinByteString
unCurrencySymbol CurrencySymbol
cs