{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}

module Test.Cardano.Chain.UTxO.Example (
  exampleTxAux,
  exampleTxAux1,
  exampleTxId,
  exampleTxInList,
  exampleTxInUtxo,
  exampleTxPayload,
  exampleTxPayload1,
  exampleTxProof,
  exampleTxOut,
  exampleTxOut1,
  exampleTxOutList,
  exampleTxSig,
  exampleTxSigData,
  exampleTxWitness,
  exampleRedeemSignature,
  exampleHashTx,
)
where

import Cardano.Chain.Common (
  NetworkMagic (..),
  makeVerKeyAddress,
  mkAttributes,
  mkKnownLovelace,
  mkMerkleTree,
  mtRoot,
 )
import Cardano.Chain.UTxO (
  Tx (..),
  TxAux,
  TxId,
  TxIn (..),
  TxInWitness (..),
  TxOut (..),
  TxPayload,
  TxProof (..),
  TxSig,
  TxSigData (..),
  TxWitness,
  mkTxAux,
  mkTxPayload,
 )
import Cardano.Crypto (
  Hash,
  ProtocolMagicId (..),
  RedeemSignature,
  SignTag (..),
  VerificationKey (..),
  redeemDeterministicKeyGen,
  redeemSign,
  serializeCborHash,
  sign,
 )
import qualified Cardano.Crypto.Wallet as CC
import Cardano.Prelude
import Data.Coerce (coerce)
import Data.List.NonEmpty (fromList)
import Data.Maybe (fromJust)
import qualified Data.Vector as V
import Test.Cardano.Crypto.CBOR (getBytes)
import Test.Cardano.Crypto.Example (exampleSigningKey, exampleVerificationKey)

exampleTxAux :: TxAux
exampleTxAux :: TxAux
exampleTxAux = Tx -> TxWitness -> TxAux
mkTxAux Tx
tx TxWitness
exampleTxWitness
  where
    tx :: Tx
tx = NonEmpty TxIn -> NonEmpty TxOut -> TxAttributes -> Tx
UnsafeTx NonEmpty TxIn
exampleTxInList NonEmpty TxOut
exampleTxOutList (forall h. h -> Attributes h
mkAttributes ())

exampleTxAux1 :: TxAux
exampleTxAux1 :: TxAux
exampleTxAux1 = Tx -> TxWitness -> TxAux
mkTxAux Tx
tx TxWitness
exampleTxWitness
  where
    tx :: Tx
tx = NonEmpty TxIn -> NonEmpty TxOut -> TxAttributes -> Tx
UnsafeTx NonEmpty TxIn
exampleTxInList1 NonEmpty TxOut
exampleTxOutList1 (forall h. h -> Attributes h
mkAttributes ())

exampleTxId :: TxId
exampleTxId :: Hash Tx
exampleTxId = Hash Tx
exampleHashTx

exampleTxInList :: (NonEmpty TxIn)
exampleTxInList :: NonEmpty TxIn
exampleTxInList = forall a. [a] -> NonEmpty a
fromList [TxIn
exampleTxInUtxo]

exampleTxInList1 :: (NonEmpty TxIn)
exampleTxInList1 :: NonEmpty TxIn
exampleTxInList1 = forall a. [a] -> NonEmpty a
fromList [TxIn
exampleTxInUtxo, TxIn
exampleTxInUtxo1]

exampleTxInUtxo :: TxIn
exampleTxInUtxo :: TxIn
exampleTxInUtxo = Hash Tx -> Word16 -> TxIn
TxInUtxo Hash Tx
exampleHashTx Word16
47 -- TODO: loop here

exampleTxInUtxo1 :: TxIn
exampleTxInUtxo1 :: TxIn
exampleTxInUtxo1 = Hash Tx -> Word16 -> TxIn
TxInUtxo Hash Tx
exampleHashTx Word16
74

exampleTxOut :: TxOut
exampleTxOut :: TxOut
exampleTxOut =
  Address -> Lovelace -> TxOut
TxOut
    (NetworkMagic -> VerificationKey -> Address
makeVerKeyAddress NetworkMagic
NetworkMainOrStage VerificationKey
vkey)
    (forall (n :: Nat). (KnownNat n, n <= 45000000000000000) => Lovelace
mkKnownLovelace @47)
  where
    Right VerificationKey
vkey = XPub -> VerificationKey
VerificationKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Either String XPub
CC.xpub (Int -> Int -> ByteString
getBytes Int
0 Int
64)

exampleTxOut1 :: TxOut
exampleTxOut1 :: TxOut
exampleTxOut1 = Address -> Lovelace -> TxOut
TxOut (NetworkMagic -> VerificationKey -> Address
makeVerKeyAddress (Word32 -> NetworkMagic
NetworkTestnet Word32
74) VerificationKey
vkey) (forall (n :: Nat). (KnownNat n, n <= 45000000000000000) => Lovelace
mkKnownLovelace @47)
  where
    Right VerificationKey
vkey = XPub -> VerificationKey
VerificationKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Either String XPub
CC.xpub (Int -> Int -> ByteString
getBytes Int
0 Int
64)

exampleTxOutList :: (NonEmpty TxOut)
exampleTxOutList :: NonEmpty TxOut
exampleTxOutList = forall a. [a] -> NonEmpty a
fromList [TxOut
exampleTxOut]

exampleTxOutList1 :: (NonEmpty TxOut)
exampleTxOutList1 :: NonEmpty TxOut
exampleTxOutList1 = forall a. [a] -> NonEmpty a
fromList [TxOut
exampleTxOut, TxOut
exampleTxOut1]

exampleTxPayload :: TxPayload
exampleTxPayload :: TxPayload
exampleTxPayload = [TxAux] -> TxPayload
mkTxPayload [TxAux
exampleTxAux]

exampleTxPayload1 :: TxPayload
exampleTxPayload1 :: TxPayload
exampleTxPayload1 = [TxAux] -> TxPayload
mkTxPayload [TxAux
exampleTxAux, TxAux
exampleTxAux1]

exampleTxProof :: TxProof
exampleTxProof :: TxProof
exampleTxProof = Word32 -> MerkleRoot Tx -> Hash [TxWitness] -> TxProof
TxProof Word32
32 MerkleRoot Tx
mroot Hash [TxWitness]
hashWit
  where
    mroot :: MerkleRoot Tx
mroot =
      forall a. MerkleTree a -> MerkleRoot a
mtRoot
        forall a b. (a -> b) -> a -> b
$ forall a. EncCBOR a => [a] -> MerkleTree a
mkMerkleTree
          [(NonEmpty TxIn -> NonEmpty TxOut -> TxAttributes -> Tx
UnsafeTx NonEmpty TxIn
exampleTxInList NonEmpty TxOut
exampleTxOutList (forall h. h -> Attributes h
mkAttributes ()))]
    hashWit :: Hash [TxWitness]
hashWit = forall a. EncCBOR a => a -> Hash a
serializeCborHash forall a b. (a -> b) -> a -> b
$ [(forall a. [a] -> Vector a
V.fromList [(VerificationKey -> TxSig -> TxInWitness
VKWitness VerificationKey
exampleVerificationKey TxSig
exampleTxSig)])]

exampleTxSig :: TxSig
exampleTxSig :: TxSig
exampleTxSig =
  forall a.
EncCBOR a =>
ProtocolMagicId -> SignTag -> SigningKey -> a -> Signature a
sign (Word32 -> ProtocolMagicId
ProtocolMagicId Word32
0) SignTag
SignForTestingOnly SigningKey
exampleSigningKey TxSigData
exampleTxSigData

exampleTxSigData :: TxSigData
exampleTxSigData :: TxSigData
exampleTxSigData = Hash Tx -> TxSigData
TxSigData Hash Tx
exampleHashTx

exampleTxWitness :: TxWitness
exampleTxWitness :: TxWitness
exampleTxWitness = forall a. [a] -> Vector a
V.fromList [(VerificationKey -> TxSig -> TxInWitness
VKWitness VerificationKey
exampleVerificationKey TxSig
exampleTxSig)]

exampleRedeemSignature :: RedeemSignature TxSigData
exampleRedeemSignature :: RedeemSignature TxSigData
exampleRedeemSignature =
  forall a.
EncCBOR a =>
ProtocolMagicId
-> SignTag -> RedeemSigningKey -> a -> RedeemSignature a
redeemSign
    (Word32 -> ProtocolMagicId
ProtocolMagicId Word32
0)
    SignTag
SignForTestingOnly
    RedeemSigningKey
rsk
    TxSigData
exampleTxSigData
  where
    rsk :: RedeemSigningKey
rsk = forall a. HasCallStack => Maybe a -> a
fromJust (forall a b. (a, b) -> b
snd forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (RedeemVerificationKey, RedeemSigningKey)
redeemDeterministicKeyGen (Int -> Int -> ByteString
getBytes Int
0 Int
32))

exampleHashTx :: Hash Tx
exampleHashTx :: Hash Tx
exampleHashTx = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. EncCBOR a => a -> Hash a
serializeCborHash Text
"golden" :: Hash Text)