{-# LANGUAGE DataKinds #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UndecidableInstances #-} {-# OPTIONS_GHC -Wno-orphans #-} module Cardano.Ledger.Mary.TxWits () where import Cardano.Ledger.Core (EraTxWits (..), upgradeScript) import Cardano.Ledger.Crypto (Crypto, StandardCrypto) import Cardano.Ledger.Mary.Era (MaryEra) import Cardano.Ledger.Mary.TxAuxData () import Cardano.Ledger.Shelley.TxWits ( ShelleyTxWits (..), addrShelleyTxWitsL, bootAddrShelleyTxWitsL, scriptShelleyTxWitsL, ) instance Crypto c => EraTxWits (MaryEra c) where {-# SPECIALIZE instance EraTxWits (MaryEra StandardCrypto) #-} type TxWits (MaryEra c) = ShelleyTxWits (MaryEra c) mkBasicTxWits :: TxWits (MaryEra c) mkBasicTxWits = forall a. Monoid a => a mempty addrTxWitsL :: Lens' (TxWits (MaryEra c)) (Set (WitVKey 'Witness (EraCrypto (MaryEra c)))) addrTxWitsL = forall era. EraScript era => Lens' (ShelleyTxWits era) (Set (WitVKey 'Witness (EraCrypto era))) addrShelleyTxWitsL {-# INLINE addrTxWitsL #-} bootAddrTxWitsL :: Lens' (TxWits (MaryEra c)) (Set (BootstrapWitness (EraCrypto (MaryEra c)))) bootAddrTxWitsL = forall era. EraScript era => Lens' (ShelleyTxWits era) (Set (BootstrapWitness (EraCrypto era))) bootAddrShelleyTxWitsL {-# INLINE bootAddrTxWitsL #-} scriptTxWitsL :: Lens' (TxWits (MaryEra c)) (Map (ScriptHash (EraCrypto (MaryEra c))) (Script (MaryEra c))) scriptTxWitsL = forall era. EraScript era => Lens' (ShelleyTxWits era) (Map (ScriptHash (EraCrypto era)) (Script era)) scriptShelleyTxWitsL {-# INLINE scriptTxWitsL #-} upgradeTxWits :: EraTxWits (PreviousEra (MaryEra c)) => TxWits (PreviousEra (MaryEra c)) -> TxWits (MaryEra c) upgradeTxWits TxWits (PreviousEra (MaryEra c)) stw = forall era. EraScript era => Set (WitVKey 'Witness (EraCrypto era)) -> Map (ScriptHash (EraCrypto era)) (Script era) -> Set (BootstrapWitness (EraCrypto era)) -> ShelleyTxWits era ShelleyTxWits (forall era. EraScript era => ShelleyTxWits era -> Set (WitVKey 'Witness (EraCrypto era)) addrWits TxWits (PreviousEra (MaryEra c)) stw) (forall era. (EraScript era, EraScript (PreviousEra era)) => Script (PreviousEra era) -> Script era upgradeScript forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> forall era. EraScript era => ShelleyTxWits era -> Map (ScriptHash (EraCrypto era)) (Script era) scriptWits TxWits (PreviousEra (MaryEra c)) stw) (forall era. EraScript era => ShelleyTxWits era -> Set (BootstrapWitness (EraCrypto era)) bootWits TxWits (PreviousEra (MaryEra c)) stw)