Skip to content

Commit

Permalink
Group UTxO-related modules
Browse files Browse the repository at this point in the history
  • Loading branch information
HeinrichApfelmus committed Apr 25, 2024
1 parent 7970de0 commit 83fd58b
Show file tree
Hide file tree
Showing 16 changed files with 50 additions and 45 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -3,4 +3,8 @@ module Cardano.Wallet.Deposit.Everything where
import Cardano.Wallet.Deposit.Pure
import Cardano.Wallet.Deposit.Pure.Timeline
import Cardano.Wallet.Deposit.Pure.TxSummary
import Cardano.Wallet.Deposit.Pure.ValueTransfer

import Cardano.Wallet.Deposit.Pure.UTxO.Balance
import Cardano.Wallet.Deposit.Pure.UTxO.DeltaUTxO
import Cardano.Wallet.Deposit.Pure.UTxO.UTxO
import Cardano.Wallet.Deposit.Pure.UTxO.ValueTransfer
Original file line number Diff line number Diff line change
Expand Up @@ -33,26 +33,26 @@ import Cardano.Wallet.Deposit.Pure.Address
( Customer
, AddressState
)
import Cardano.Wallet.Deposit.Pure.UTxO
import Cardano.Wallet.Deposit.Pure.UTxO.UTxO
( UTxO
)
import Cardano.Wallet.Deposit.Pure.TxSummary
( TxSummary
)
import qualified Cardano.Wallet.Deposit.Pure.Address as Addr
import qualified Cardano.Wallet.Deposit.Pure.Balance as Balance
import qualified Cardano.Wallet.Deposit.Pure.UTxO as UTxO
import qualified Cardano.Wallet.Deposit.Pure.UTxO.Balance as Balance
import qualified Cardano.Wallet.Deposit.Pure.UTxO.UTxO as UTxO
#-}

open import Cardano.Wallet.Deposit.Pure.Address using
( Customer
; deriveCustomerAddress
; AddressState
)
open import Cardano.Wallet.Deposit.Pure.UTxO using
open import Cardano.Wallet.Deposit.Pure.UTxO.UTxO using
( UTxO
)
open import Cardano.Wallet.Deposit.Pure.ValueTransfer using
open import Cardano.Wallet.Deposit.Pure.UTxO.ValueTransfer using
( ValueTransfer
; fromSpent
; fromReceived
Expand Down Expand Up @@ -91,8 +91,8 @@ open import Haskell.Data.Maybe using
)

import Cardano.Wallet.Deposit.Pure.Address as Addr
import Cardano.Wallet.Deposit.Pure.Balance as Balance
import Cardano.Wallet.Deposit.Pure.UTxO as UTxO
import Cardano.Wallet.Deposit.Pure.UTxO.Balance as Balance
import Cardano.Wallet.Deposit.Pure.UTxO.UTxO as UTxO
import Haskell.Data.Map as Map

-- The import of the cong! tactic slows down type checking…
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@ module Cardano.Wallet.Deposit.Pure.TxSummary where

open import Haskell.Prelude

open import Cardano.Wallet.Deposit.Pure.ValueTransfer using
open import Cardano.Wallet.Deposit.Pure.UTxO.ValueTransfer using
( ValueTransfer
)
open import Cardano.Wallet.Deposit.Read using
Expand Down
Original file line number Diff line number Diff line change
@@ -1,22 +1,22 @@
{-# OPTIONS --erasure #-}

module Cardano.Wallet.Deposit.Pure.Balance where
module Cardano.Wallet.Deposit.Pure.UTxO.Balance where

open import Haskell.Prelude

open import Cardano.Wallet.Deposit.Pure.UTxO using
open import Cardano.Wallet.Deposit.Pure.UTxO.UTxO using
( UTxO
)
open import Cardano.Wallet.Deposit.Pure.DeltaUTxO using
open import Cardano.Wallet.Deposit.Pure.UTxO.DeltaUTxO using
( DeltaUTxO
)
open import Cardano.Wallet.Deposit.Read using
( Tx
; TxBody
)

import Cardano.Wallet.Deposit.Pure.DeltaUTxO as DeltaUTxO
import Cardano.Wallet.Deposit.Pure.UTxO as UTxO
import Cardano.Wallet.Deposit.Pure.UTxO.DeltaUTxO as DeltaUTxO
import Cardano.Wallet.Deposit.Pure.UTxO.UTxO as UTxO
import Cardano.Wallet.Deposit.Read as Read
import Haskell.Data.Map as Map
import Haskell.Data.Set as Set
Expand Down
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
{-# OPTIONS --erasure #-}

module Cardano.Wallet.Deposit.Pure.DeltaUTxO
module Cardano.Wallet.Deposit.Pure.UTxO.DeltaUTxO
{-
; DeltaUTxO
; null
Expand All @@ -18,14 +18,14 @@ open import Haskell.Prelude hiding
)
open import Haskell.Reasoning

open import Cardano.Wallet.Deposit.Pure.UTxO using
open import Cardano.Wallet.Deposit.Pure.UTxO.UTxO using
( UTxO
)
open import Cardano.Wallet.Deposit.Read using
( TxIn
)

import Cardano.Wallet.Deposit.Pure.UTxO as UTxO
import Cardano.Wallet.Deposit.Pure.UTxO.UTxO as UTxO
import Haskell.Data.Map as Map
import Haskell.Data.Set as Set

Expand Down
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
{-# OPTIONS --erasure #-}

module Cardano.Wallet.Deposit.Pure.UTxO
module Cardano.Wallet.Deposit.Pure.UTxO.UTxO
{-
; UTxO
; null
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module Cardano.Wallet.Deposit.Pure.ValueTransfer where
module Cardano.Wallet.Deposit.Pure.UTxO.ValueTransfer where

open import Haskell.Prelude

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ module Cardano.Write.Tx.Balance
open import Haskell.Prelude
open import Haskell.Reasoning

open import Cardano.Wallet.Deposit.Pure.UTxO using
open import Cardano.Wallet.Deposit.Pure.UTxO.UTxO using
( UTxO
)
open import Cardano.Wallet.Deposit.Read using
Expand All @@ -30,7 +30,7 @@ open import Cardano.Wallet.Deposit.Read using
open import Haskell.Data.List.Prop using ( _∈_ )
open import Haskell.Data.Maybe using ( isJust )

import Cardano.Wallet.Deposit.Pure.UTxO as UTxO
import Cardano.Wallet.Deposit.Pure.UTxO.UTxO as UTxO
import Haskell.Data.ByteString as BS
import Haskell.Data.Map as Map

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -59,12 +59,12 @@ library
exposed-modules:
Cardano.Wallet.Deposit.Pure
Cardano.Wallet.Deposit.Pure.Address
Cardano.Wallet.Deposit.Pure.Balance
Cardano.Wallet.Deposit.Pure.DeltaUTxO
Cardano.Wallet.Deposit.Pure.UTxO
Cardano.Wallet.Deposit.Pure.UTxO.Balance
Cardano.Wallet.Deposit.Pure.UTxO.DeltaUTxO
Cardano.Wallet.Deposit.Pure.UTxO.UTxO
Cardano.Wallet.Deposit.Pure.UTxO.ValueTransfer
Cardano.Wallet.Deposit.Pure.Timeline
Cardano.Wallet.Deposit.Pure.TxSummary
Cardano.Wallet.Deposit.Pure.ValueTransfer
Cardano.Wallet.Deposit.Read
Cardano.Write.Tx.Balance
other-modules:
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -9,15 +9,15 @@ import Cardano.Wallet.Deposit.Pure.Address
( Customer
, AddressState
)
import Cardano.Wallet.Deposit.Pure.UTxO
import Cardano.Wallet.Deposit.Pure.UTxO.UTxO
( UTxO
)
import Cardano.Wallet.Deposit.Pure.TxSummary
( TxSummary
)
import qualified Cardano.Wallet.Deposit.Pure.Address as Addr
import qualified Cardano.Wallet.Deposit.Pure.Balance as Balance
import qualified Cardano.Wallet.Deposit.Pure.UTxO as UTxO
import qualified Cardano.Wallet.Deposit.Pure.UTxO.Balance as Balance
import qualified Cardano.Wallet.Deposit.Pure.UTxO.UTxO as UTxO

data WalletState = WalletState{addresses :: AddressState,
utxo :: UTxO, txSummaries :: Map.Map Customer [TxSummary],
Expand Down
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
module Cardano.Wallet.Deposit.Pure.TxSummary where

import Cardano.Wallet.Deposit.Pure.ValueTransfer (ValueTransfer)
import Cardano.Wallet.Deposit.Pure.UTxO.ValueTransfer (ValueTransfer)
import Cardano.Wallet.Deposit.Read (ChainPoint(GenesisPoint), Tx(txid), TxId)

data TxSummary = TxSummary{summarizedTx :: TxId,
Expand Down
Original file line number Diff line number Diff line change
@@ -1,9 +1,9 @@
module Cardano.Wallet.Deposit.Pure.Balance where
module Cardano.Wallet.Deposit.Pure.UTxO.Balance where

import Cardano.Wallet.Deposit.Pure.DeltaUTxO (DeltaUTxO)
import qualified Cardano.Wallet.Deposit.Pure.DeltaUTxO (excludingD, null, receiveD)
import Cardano.Wallet.Deposit.Pure.UTxO (UTxO)
import qualified Cardano.Wallet.Deposit.Pure.UTxO as UTxO (filterByAddress, null)
import Cardano.Wallet.Deposit.Pure.UTxO.DeltaUTxO (DeltaUTxO)
import qualified Cardano.Wallet.Deposit.Pure.UTxO.DeltaUTxO (excludingD, null, receiveD)
import Cardano.Wallet.Deposit.Pure.UTxO.UTxO (UTxO)
import qualified Cardano.Wallet.Deposit.Pure.UTxO.UTxO as UTxO (filterByAddress, null)
import Cardano.Wallet.Deposit.Read (Tx(txbody, txid), TxBody(inputs, outputs))
import qualified Cardano.Wallet.Deposit.Read as Read (Addr, TxIn, TxOut)
import Data.Set (Set)
Expand All @@ -13,7 +13,7 @@ import qualified Haskell.Data.Set as Set (fromList)

spendTxD :: Tx -> UTxO -> (DeltaUTxO, UTxO)
spendTxD tx u
= Cardano.Wallet.Deposit.Pure.DeltaUTxO.excludingD u
= Cardano.Wallet.Deposit.Pure.UTxO.DeltaUTxO.excludingD u
inputsToExclude
where
inputsToExclude :: Set Read.TxIn
Expand All @@ -35,15 +35,16 @@ applyTx :: IsOurs Read.Addr -> Tx -> UTxO -> (DeltaUTxO, UTxO)
applyTx isOurs tx u0
= if
UTxO.null (UTxO.filterByAddress isOurs (utxoFromTxOutputs tx)) &&
Cardano.Wallet.Deposit.Pure.DeltaUTxO.null (fst (spendTxD tx u0))
Cardano.Wallet.Deposit.Pure.UTxO.DeltaUTxO.null
(fst (spendTxD tx u0))
then (mempty, u0) else
(fst
(Cardano.Wallet.Deposit.Pure.DeltaUTxO.receiveD
(Cardano.Wallet.Deposit.Pure.UTxO.DeltaUTxO.receiveD
(snd (spendTxD tx u0))
(UTxO.filterByAddress isOurs (utxoFromTxOutputs tx)))
<> fst (spendTxD tx u0),
snd
(Cardano.Wallet.Deposit.Pure.DeltaUTxO.receiveD
(Cardano.Wallet.Deposit.Pure.UTxO.DeltaUTxO.receiveD
(snd (spendTxD tx u0))
(UTxO.filterByAddress isOurs (utxoFromTxOutputs tx))))

Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
module Cardano.Wallet.Deposit.Pure.DeltaUTxO where
module Cardano.Wallet.Deposit.Pure.UTxO.DeltaUTxO where

import Cardano.Wallet.Deposit.Pure.UTxO (UTxO)
import qualified Cardano.Wallet.Deposit.Pure.UTxO as UTxO (empty, excluding, excludingS, null, union)
import Cardano.Wallet.Deposit.Pure.UTxO.UTxO (UTxO)
import qualified Cardano.Wallet.Deposit.Pure.UTxO.UTxO as UTxO (empty, excluding, excludingS, null, union)
import Cardano.Wallet.Deposit.Read (TxIn)
import Data.Set (Set)
import qualified Haskell.Data.Map as Map (empty, keysSet)
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module Cardano.Wallet.Deposit.Pure.UTxO where
module Cardano.Wallet.Deposit.Pure.UTxO.UTxO where

import Cardano.Wallet.Deposit.Read (Address, TxIn, TxOut(address, value), Value)
import Data.Set (Set)
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module Cardano.Wallet.Deposit.Pure.ValueTransfer where
module Cardano.Wallet.Deposit.Pure.UTxO.ValueTransfer where

import Cardano.Wallet.Deposit.Read (Value)

Expand Down
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
module Cardano.Write.Tx.Balance where

import Cardano.Wallet.Deposit.Pure.UTxO (UTxO)
import qualified Cardano.Wallet.Deposit.Pure.UTxO as UTxO (balance)
import Cardano.Wallet.Deposit.Pure.UTxO.UTxO (UTxO)
import qualified Cardano.Wallet.Deposit.Pure.UTxO.UTxO as UTxO (balance)
import Cardano.Wallet.Deposit.Read (Address, TxBody(TxBodyC), TxIn, TxOut(TxOutC, value), Value, exceeds, minus)
import qualified Haskell.Data.Map as Map (toAscList)

Expand Down

0 comments on commit 83fd58b

Please sign in to comment.