{-# 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.Mary.Era (MaryEra)
import Cardano.Ledger.Mary.TxAuxData ()
import Cardano.Ledger.Shelley.TxWits (
  ShelleyTxWits (..),
  addrShelleyTxWitsL,
  bootAddrShelleyTxWitsL,
  scriptShelleyTxWitsL,
 )

instance EraTxWits MaryEra where
  type TxWits MaryEra = ShelleyTxWits MaryEra

  mkBasicTxWits :: TxWits MaryEra
mkBasicTxWits = TxWits MaryEra
ShelleyTxWits MaryEra
forall a. Monoid a => a
mempty

  addrTxWitsL :: Lens' (TxWits MaryEra) (Set (WitVKey 'Witness))
addrTxWitsL = (Set (WitVKey 'Witness) -> f (Set (WitVKey 'Witness)))
-> TxWits MaryEra -> f (TxWits MaryEra)
(Set (WitVKey 'Witness) -> f (Set (WitVKey 'Witness)))
-> ShelleyTxWits MaryEra -> f (ShelleyTxWits MaryEra)
forall era.
EraScript era =>
Lens' (ShelleyTxWits era) (Set (WitVKey 'Witness))
Lens' (ShelleyTxWits MaryEra) (Set (WitVKey 'Witness))
addrShelleyTxWitsL
  {-# INLINE addrTxWitsL #-}

  bootAddrTxWitsL :: Lens' (TxWits MaryEra) (Set BootstrapWitness)
bootAddrTxWitsL = (Set BootstrapWitness -> f (Set BootstrapWitness))
-> TxWits MaryEra -> f (TxWits MaryEra)
(Set BootstrapWitness -> f (Set BootstrapWitness))
-> ShelleyTxWits MaryEra -> f (ShelleyTxWits MaryEra)
forall era.
EraScript era =>
Lens' (ShelleyTxWits era) (Set BootstrapWitness)
Lens' (ShelleyTxWits MaryEra) (Set BootstrapWitness)
bootAddrShelleyTxWitsL
  {-# INLINE bootAddrTxWitsL #-}

  scriptTxWitsL :: Lens' (TxWits MaryEra) (Map ScriptHash (Script MaryEra))
scriptTxWitsL = (Map ScriptHash (Script MaryEra)
 -> f (Map ScriptHash (Script MaryEra)))
-> TxWits MaryEra -> f (TxWits MaryEra)
(Map ScriptHash (Script MaryEra)
 -> f (Map ScriptHash (Script MaryEra)))
-> ShelleyTxWits MaryEra -> f (ShelleyTxWits MaryEra)
forall era.
EraScript era =>
Lens' (ShelleyTxWits era) (Map ScriptHash (Script era))
Lens' (ShelleyTxWits MaryEra) (Map ScriptHash (Script MaryEra))
scriptShelleyTxWitsL
  {-# INLINE scriptTxWitsL #-}

  upgradeTxWits :: EraTxWits (PreviousEra MaryEra) =>
TxWits (PreviousEra MaryEra) -> TxWits MaryEra
upgradeTxWits TxWits (PreviousEra MaryEra)
stw =
    Set (WitVKey 'Witness)
-> Map ScriptHash (Script MaryEra)
-> Set BootstrapWitness
-> ShelleyTxWits MaryEra
forall era.
EraScript era =>
Set (WitVKey 'Witness)
-> Map ScriptHash (Script era)
-> Set BootstrapWitness
-> ShelleyTxWits era
ShelleyTxWits
      (ShelleyTxWits AllegraEra -> Set (WitVKey 'Witness)
forall era.
EraScript era =>
ShelleyTxWits era -> Set (WitVKey 'Witness)
addrWits TxWits (PreviousEra MaryEra)
ShelleyTxWits AllegraEra
stw)
      (Script (PreviousEra MaryEra) -> Timelock MaryEra
Script (PreviousEra MaryEra) -> Script MaryEra
forall era.
(EraScript era, EraScript (PreviousEra era)) =>
Script (PreviousEra era) -> Script era
upgradeScript (Script (PreviousEra MaryEra) -> Timelock MaryEra)
-> Map ScriptHash (Script (PreviousEra MaryEra))
-> Map ScriptHash (Timelock MaryEra)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ShelleyTxWits AllegraEra -> Map ScriptHash (Script AllegraEra)
forall era.
EraScript era =>
ShelleyTxWits era -> Map ScriptHash (Script era)
scriptWits TxWits (PreviousEra MaryEra)
ShelleyTxWits AllegraEra
stw)
      (ShelleyTxWits AllegraEra -> Set BootstrapWitness
forall era.
EraScript era =>
ShelleyTxWits era -> Set BootstrapWitness
bootWits TxWits (PreviousEra MaryEra)
ShelleyTxWits AllegraEra
stw)