{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
module Cardano.Wallet.DB.Store.Meta.Model
( DeltaTxMetaHistory(..)
, ManipulateTxMetaHistory(..)
, TxMetaHistory(..)
, mkTxMetaHistory
)
where
import Prelude
import Cardano.Wallet.DB.Sqlite.Schema
( TxMeta (..) )
import Cardano.Wallet.DB.Sqlite.Types
( TxId (..) )
import Control.Monad
( MonadPlus (mzero) )
import Data.Delta
( Delta (..) )
import Data.Functor
( (<&>) )
import Data.Generics.Internal.VL
( (^.) )
import Data.Map.Strict
( Map )
import Data.Quantity
( Quantity (getQuantity) )
import Fmt
( Buildable (build) )
import GHC.Generics
( Generic )
import qualified Cardano.Wallet.Primitive.Types as W
import qualified Cardano.Wallet.Primitive.Types.Coin as W
import qualified Cardano.Wallet.Primitive.Types.Tx as W
import qualified Data.Map.Strict as Map
newtype TxMetaHistory =
TxMetaHistory { TxMetaHistory -> Map TxId TxMeta
relations :: Map TxId TxMeta }
deriving ( (forall x. TxMetaHistory -> Rep TxMetaHistory x)
-> (forall x. Rep TxMetaHistory x -> TxMetaHistory)
-> Generic TxMetaHistory
forall x. Rep TxMetaHistory x -> TxMetaHistory
forall x. TxMetaHistory -> Rep TxMetaHistory x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TxMetaHistory x -> TxMetaHistory
$cfrom :: forall x. TxMetaHistory -> Rep TxMetaHistory x
Generic, TxMetaHistory -> TxMetaHistory -> Bool
(TxMetaHistory -> TxMetaHistory -> Bool)
-> (TxMetaHistory -> TxMetaHistory -> Bool) -> Eq TxMetaHistory
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TxMetaHistory -> TxMetaHistory -> Bool
$c/= :: TxMetaHistory -> TxMetaHistory -> Bool
== :: TxMetaHistory -> TxMetaHistory -> Bool
$c== :: TxMetaHistory -> TxMetaHistory -> Bool
Eq, Int -> TxMetaHistory -> ShowS
[TxMetaHistory] -> ShowS
TxMetaHistory -> String
(Int -> TxMetaHistory -> ShowS)
-> (TxMetaHistory -> String)
-> ([TxMetaHistory] -> ShowS)
-> Show TxMetaHistory
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TxMetaHistory] -> ShowS
$cshowList :: [TxMetaHistory] -> ShowS
show :: TxMetaHistory -> String
$cshow :: TxMetaHistory -> String
showsPrec :: Int -> TxMetaHistory -> ShowS
$cshowsPrec :: Int -> TxMetaHistory -> ShowS
Show, Semigroup TxMetaHistory
TxMetaHistory
Semigroup TxMetaHistory
-> TxMetaHistory
-> (TxMetaHistory -> TxMetaHistory -> TxMetaHistory)
-> ([TxMetaHistory] -> TxMetaHistory)
-> Monoid TxMetaHistory
[TxMetaHistory] -> TxMetaHistory
TxMetaHistory -> TxMetaHistory -> TxMetaHistory
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
mconcat :: [TxMetaHistory] -> TxMetaHistory
$cmconcat :: [TxMetaHistory] -> TxMetaHistory
mappend :: TxMetaHistory -> TxMetaHistory -> TxMetaHistory
$cmappend :: TxMetaHistory -> TxMetaHistory -> TxMetaHistory
mempty :: TxMetaHistory
$cmempty :: TxMetaHistory
$cp1Monoid :: Semigroup TxMetaHistory
Monoid, b -> TxMetaHistory -> TxMetaHistory
NonEmpty TxMetaHistory -> TxMetaHistory
TxMetaHistory -> TxMetaHistory -> TxMetaHistory
(TxMetaHistory -> TxMetaHistory -> TxMetaHistory)
-> (NonEmpty TxMetaHistory -> TxMetaHistory)
-> (forall b. Integral b => b -> TxMetaHistory -> TxMetaHistory)
-> Semigroup TxMetaHistory
forall b. Integral b => b -> TxMetaHistory -> TxMetaHistory
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: b -> TxMetaHistory -> TxMetaHistory
$cstimes :: forall b. Integral b => b -> TxMetaHistory -> TxMetaHistory
sconcat :: NonEmpty TxMetaHistory -> TxMetaHistory
$csconcat :: NonEmpty TxMetaHistory -> TxMetaHistory
<> :: TxMetaHistory -> TxMetaHistory -> TxMetaHistory
$c<> :: TxMetaHistory -> TxMetaHistory -> TxMetaHistory
Semigroup )
instance Buildable TxMetaHistory where
build :: TxMetaHistory -> Builder
build TxMetaHistory
txs =
Builder
"TxMetaHistory "
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Int -> Builder
forall p. Buildable p => p -> Builder
build (Map TxId TxMeta -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (Map TxId TxMeta -> Int) -> Map TxId TxMeta -> Int
forall a b. (a -> b) -> a -> b
$ TxMetaHistory -> Map TxId TxMeta
relations TxMetaHistory
txs)
data ManipulateTxMetaHistory
= PruneTxMetaHistory TxId
| AgeTxMetaHistory W.SlotNo
| RollBackTxMetaHistory W.SlotNo
deriving ( ManipulateTxMetaHistory -> ManipulateTxMetaHistory -> Bool
(ManipulateTxMetaHistory -> ManipulateTxMetaHistory -> Bool)
-> (ManipulateTxMetaHistory -> ManipulateTxMetaHistory -> Bool)
-> Eq ManipulateTxMetaHistory
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ManipulateTxMetaHistory -> ManipulateTxMetaHistory -> Bool
$c/= :: ManipulateTxMetaHistory -> ManipulateTxMetaHistory -> Bool
== :: ManipulateTxMetaHistory -> ManipulateTxMetaHistory -> Bool
$c== :: ManipulateTxMetaHistory -> ManipulateTxMetaHistory -> Bool
Eq, Int -> ManipulateTxMetaHistory -> ShowS
[ManipulateTxMetaHistory] -> ShowS
ManipulateTxMetaHistory -> String
(Int -> ManipulateTxMetaHistory -> ShowS)
-> (ManipulateTxMetaHistory -> String)
-> ([ManipulateTxMetaHistory] -> ShowS)
-> Show ManipulateTxMetaHistory
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ManipulateTxMetaHistory] -> ShowS
$cshowList :: [ManipulateTxMetaHistory] -> ShowS
show :: ManipulateTxMetaHistory -> String
$cshow :: ManipulateTxMetaHistory -> String
showsPrec :: Int -> ManipulateTxMetaHistory -> ShowS
$cshowsPrec :: Int -> ManipulateTxMetaHistory -> ShowS
Show )
data DeltaTxMetaHistory
= Manipulate ManipulateTxMetaHistory
| Expand TxMetaHistory
deriving (Int -> DeltaTxMetaHistory -> ShowS
[DeltaTxMetaHistory] -> ShowS
DeltaTxMetaHistory -> String
(Int -> DeltaTxMetaHistory -> ShowS)
-> (DeltaTxMetaHistory -> String)
-> ([DeltaTxMetaHistory] -> ShowS)
-> Show DeltaTxMetaHistory
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeltaTxMetaHistory] -> ShowS
$cshowList :: [DeltaTxMetaHistory] -> ShowS
show :: DeltaTxMetaHistory -> String
$cshow :: DeltaTxMetaHistory -> String
showsPrec :: Int -> DeltaTxMetaHistory -> ShowS
$cshowsPrec :: Int -> DeltaTxMetaHistory -> ShowS
Show, DeltaTxMetaHistory -> DeltaTxMetaHistory -> Bool
(DeltaTxMetaHistory -> DeltaTxMetaHistory -> Bool)
-> (DeltaTxMetaHistory -> DeltaTxMetaHistory -> Bool)
-> Eq DeltaTxMetaHistory
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeltaTxMetaHistory -> DeltaTxMetaHistory -> Bool
$c/= :: DeltaTxMetaHistory -> DeltaTxMetaHistory -> Bool
== :: DeltaTxMetaHistory -> DeltaTxMetaHistory -> Bool
$c== :: DeltaTxMetaHistory -> DeltaTxMetaHistory -> Bool
Eq)
instance Buildable DeltaTxMetaHistory where
build :: DeltaTxMetaHistory -> Builder
build = String -> Builder
forall p. Buildable p => p -> Builder
build (String -> Builder)
-> (DeltaTxMetaHistory -> String) -> DeltaTxMetaHistory -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DeltaTxMetaHistory -> String
forall a. Show a => a -> String
show
instance Delta DeltaTxMetaHistory where
type Base DeltaTxMetaHistory = TxMetaHistory
apply :: DeltaTxMetaHistory
-> Base DeltaTxMetaHistory -> Base DeltaTxMetaHistory
apply (Expand TxMetaHistory
txs) Base DeltaTxMetaHistory
h = TxMetaHistory
txs TxMetaHistory -> TxMetaHistory -> TxMetaHistory
forall a. Semigroup a => a -> a -> a
<> Base DeltaTxMetaHistory
TxMetaHistory
h
apply (Manipulate ManipulateTxMetaHistory
d) Base DeltaTxMetaHistory
h = ManipulateTxMetaHistory
-> Base ManipulateTxMetaHistory -> Base ManipulateTxMetaHistory
forall delta. Delta delta => delta -> Base delta -> Base delta
apply ManipulateTxMetaHistory
d Base DeltaTxMetaHistory
Base ManipulateTxMetaHistory
h
instance Delta ManipulateTxMetaHistory where
type Base ManipulateTxMetaHistory = TxMetaHistory
apply :: ManipulateTxMetaHistory
-> Base ManipulateTxMetaHistory -> Base ManipulateTxMetaHistory
apply (PruneTxMetaHistory TxId
tid) (TxMetaHistory txs) =
Map TxId TxMeta -> TxMetaHistory
TxMetaHistory (Map TxId TxMeta -> TxMetaHistory)
-> Map TxId TxMeta -> TxMetaHistory
forall a b. (a -> b) -> a -> b
$ (Maybe TxMeta -> Maybe TxMeta)
-> TxId -> Map TxId TxMeta -> Map TxId TxMeta
forall k a.
Ord k =>
(Maybe a -> Maybe a) -> k -> Map k a -> Map k a
Map.alter Maybe TxMeta -> Maybe TxMeta
f TxId
tid Map TxId TxMeta
txs
where
f :: Maybe TxMeta -> Maybe TxMeta
f (Just tx :: TxMeta
tx@(TxMeta {Maybe Bool
Maybe Word64
Maybe TxMetadata
Maybe SlotNo
Word32
SlotNo
Coin
Direction
TxStatus
WalletId
TxId
txMetaScriptValidity :: TxMeta -> Maybe Bool
txMetaFee :: TxMeta -> Maybe Word64
txMetaSlotExpires :: TxMeta -> Maybe SlotNo
txMetadata :: TxMeta -> Maybe TxMetadata
txMetaAmount :: TxMeta -> Coin
txMetaBlockHeight :: TxMeta -> Word32
txMetaSlot :: TxMeta -> SlotNo
txMetaDirection :: TxMeta -> Direction
txMetaStatus :: TxMeta -> TxStatus
txMetaWalletId :: TxMeta -> WalletId
txMetaTxId :: TxMeta -> TxId
txMetaScriptValidity :: Maybe Bool
txMetaFee :: Maybe Word64
txMetaSlotExpires :: Maybe SlotNo
txMetadata :: Maybe TxMetadata
txMetaAmount :: Coin
txMetaBlockHeight :: Word32
txMetaSlot :: SlotNo
txMetaDirection :: Direction
txMetaStatus :: TxStatus
txMetaWalletId :: WalletId
txMetaTxId :: TxId
..})) =
if TxStatus
txMetaStatus TxStatus -> TxStatus -> Bool
forall a. Eq a => a -> a -> Bool
== TxStatus
W.InLedger
then TxMeta -> Maybe TxMeta
forall a. a -> Maybe a
Just TxMeta
tx
else Maybe TxMeta
forall a. Maybe a
Nothing
f Maybe TxMeta
Nothing = Maybe TxMeta
forall a. Maybe a
Nothing
apply (AgeTxMetaHistory SlotNo
tip) (TxMetaHistory txs) =
Map TxId TxMeta -> TxMetaHistory
TxMetaHistory
(Map TxId TxMeta -> TxMetaHistory)
-> Map TxId TxMeta -> TxMetaHistory
forall a b. (a -> b) -> a -> b
$ Map TxId TxMeta
txs Map TxId TxMeta -> (TxMeta -> TxMeta) -> Map TxId TxMeta
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \meta :: TxMeta
meta@TxMeta {Maybe Bool
Maybe Word64
Maybe TxMetadata
Maybe SlotNo
Word32
SlotNo
Coin
Direction
TxStatus
WalletId
TxId
txMetaScriptValidity :: Maybe Bool
txMetaFee :: Maybe Word64
txMetaSlotExpires :: Maybe SlotNo
txMetadata :: Maybe TxMetadata
txMetaAmount :: Coin
txMetaBlockHeight :: Word32
txMetaSlot :: SlotNo
txMetaDirection :: Direction
txMetaStatus :: TxStatus
txMetaWalletId :: WalletId
txMetaTxId :: TxId
txMetaScriptValidity :: TxMeta -> Maybe Bool
txMetaFee :: TxMeta -> Maybe Word64
txMetaSlotExpires :: TxMeta -> Maybe SlotNo
txMetadata :: TxMeta -> Maybe TxMetadata
txMetaAmount :: TxMeta -> Coin
txMetaBlockHeight :: TxMeta -> Word32
txMetaSlot :: TxMeta -> SlotNo
txMetaDirection :: TxMeta -> Direction
txMetaStatus :: TxMeta -> TxStatus
txMetaWalletId :: TxMeta -> WalletId
txMetaTxId :: TxMeta -> TxId
..} ->
if TxStatus
txMetaStatus TxStatus -> TxStatus -> Bool
forall a. Eq a => a -> a -> Bool
== TxStatus
W.Pending Bool -> Bool -> Bool
&& Maybe SlotNo -> Bool
isExpired Maybe SlotNo
txMetaSlotExpires
then TxMeta
meta { txMetaStatus :: TxStatus
txMetaStatus = TxStatus
W.Expired }
else TxMeta
meta
where
isExpired :: Maybe SlotNo -> Bool
isExpired Maybe SlotNo
Nothing = Bool
False
isExpired (Just SlotNo
tip') = SlotNo
tip' SlotNo -> SlotNo -> Bool
forall a. Ord a => a -> a -> Bool
<= SlotNo
tip
apply (RollBackTxMetaHistory SlotNo
point) (TxMetaHistory txs) =
Map TxId TxMeta -> TxMetaHistory
TxMetaHistory (Map TxId TxMeta -> TxMetaHistory)
-> Map TxId TxMeta -> TxMetaHistory
forall a b. (a -> b) -> a -> b
$ (TxMeta -> Maybe TxMeta) -> Map TxId TxMeta -> Map TxId TxMeta
forall a b k. (a -> Maybe b) -> Map k a -> Map k b
Map.mapMaybe TxMeta -> Maybe TxMeta
rescheduleOrForget Map TxId TxMeta
txs
where
rescheduleOrForget :: TxMeta -> Maybe TxMeta
rescheduleOrForget :: TxMeta -> Maybe TxMeta
rescheduleOrForget TxMeta
meta =
let
isAfter :: Bool
isAfter = TxMeta -> SlotNo
txMetaSlot TxMeta
meta SlotNo -> SlotNo -> Bool
forall a. Ord a => a -> a -> Bool
> SlotNo
point
isIncoming :: Bool
isIncoming = TxMeta -> Direction
txMetaDirection TxMeta
meta Direction -> Direction -> Bool
forall a. Eq a => a -> a -> Bool
== Direction
W.Incoming
in case (Bool
isAfter, Bool
isIncoming) of
(Bool
True,Bool
True) -> Maybe TxMeta
forall (m :: * -> *) a. MonadPlus m => m a
mzero
(Bool
True,Bool
False) -> TxMeta -> Maybe TxMeta
forall a. a -> Maybe a
Just
(TxMeta -> Maybe TxMeta) -> TxMeta -> Maybe TxMeta
forall a b. (a -> b) -> a -> b
$ TxMeta
meta
{ txMetaSlot :: SlotNo
txMetaSlot = SlotNo
point, txMetaStatus :: TxStatus
txMetaStatus = TxStatus
W.Pending }
(Bool, Bool)
_ -> TxMeta -> Maybe TxMeta
forall a. a -> Maybe a
Just TxMeta
meta
mkTxMetaEntity :: W.WalletId -> W.Tx -> W.TxMeta -> TxMeta
mkTxMetaEntity :: WalletId -> Tx -> TxMeta -> TxMeta
mkTxMetaEntity WalletId
wid Tx
tx TxMeta
derived =
TxMeta :: TxId
-> WalletId
-> TxStatus
-> Direction
-> SlotNo
-> Word32
-> Coin
-> Maybe TxMetadata
-> Maybe SlotNo
-> Maybe Word64
-> Maybe Bool
-> TxMeta
TxMeta
{ txMetaTxId :: TxId
txMetaTxId = Hash "Tx" -> TxId
TxId (Hash "Tx" -> TxId) -> Hash "Tx" -> TxId
forall a b. (a -> b) -> a -> b
$ Tx
tx Tx
-> ((Hash "Tx" -> Const (Hash "Tx") (Hash "Tx"))
-> Tx -> Const (Hash "Tx") Tx)
-> Hash "Tx"
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. IsLabel
"txId"
((Hash "Tx" -> Const (Hash "Tx") (Hash "Tx"))
-> Tx -> Const (Hash "Tx") Tx)
(Hash "Tx" -> Const (Hash "Tx") (Hash "Tx"))
-> Tx -> Const (Hash "Tx") Tx
#txId
, txMetaWalletId :: WalletId
txMetaWalletId = WalletId
wid
, txMetaStatus :: TxStatus
txMetaStatus = TxMeta
derived TxMeta
-> ((TxStatus -> Const TxStatus TxStatus)
-> TxMeta -> Const TxStatus TxMeta)
-> TxStatus
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. IsLabel
"status"
((TxStatus -> Const TxStatus TxStatus)
-> TxMeta -> Const TxStatus TxMeta)
(TxStatus -> Const TxStatus TxStatus)
-> TxMeta -> Const TxStatus TxMeta
#status
, txMetaDirection :: Direction
txMetaDirection = TxMeta
derived TxMeta
-> ((Direction -> Const Direction Direction)
-> TxMeta -> Const Direction TxMeta)
-> Direction
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. IsLabel
"direction"
((Direction -> Const Direction Direction)
-> TxMeta -> Const Direction TxMeta)
(Direction -> Const Direction Direction)
-> TxMeta -> Const Direction TxMeta
#direction
, txMetaSlot :: SlotNo
txMetaSlot = TxMeta
derived TxMeta
-> ((SlotNo -> Const SlotNo SlotNo)
-> TxMeta -> Const SlotNo TxMeta)
-> SlotNo
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. IsLabel
"slotNo"
((SlotNo -> Const SlotNo SlotNo) -> TxMeta -> Const SlotNo TxMeta)
(SlotNo -> Const SlotNo SlotNo) -> TxMeta -> Const SlotNo TxMeta
#slotNo
, txMetaBlockHeight :: Word32
txMetaBlockHeight = Quantity "block" Word32 -> Word32
forall (unit :: Symbol) a. Quantity unit a -> a
getQuantity
(TxMeta
derived TxMeta
-> ((Quantity "block" Word32
-> Const (Quantity "block" Word32) (Quantity "block" Word32))
-> TxMeta -> Const (Quantity "block" Word32) TxMeta)
-> Quantity "block" Word32
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. IsLabel
"blockHeight"
((Quantity "block" Word32
-> Const (Quantity "block" Word32) (Quantity "block" Word32))
-> TxMeta -> Const (Quantity "block" Word32) TxMeta)
(Quantity "block" Word32
-> Const (Quantity "block" Word32) (Quantity "block" Word32))
-> TxMeta -> Const (Quantity "block" Word32) TxMeta
#blockHeight)
, txMetaAmount :: Coin
txMetaAmount = TxMeta
derived TxMeta
-> ((Coin -> Const Coin Coin) -> TxMeta -> Const Coin TxMeta)
-> Coin
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. IsLabel
"amount" ((Coin -> Const Coin Coin) -> TxMeta -> Const Coin TxMeta)
(Coin -> Const Coin Coin) -> TxMeta -> Const Coin TxMeta
#amount
, txMetaFee :: Maybe Word64
txMetaFee = Natural -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Natural -> Word64) -> (Coin -> Natural) -> Coin -> Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Coin -> Natural
W.unCoin (Coin -> Word64) -> Maybe Coin -> Maybe Word64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Tx -> Maybe Coin
W.fee Tx
tx
, txMetaSlotExpires :: Maybe SlotNo
txMetaSlotExpires = TxMeta
derived TxMeta
-> ((Maybe SlotNo -> Const (Maybe SlotNo) (Maybe SlotNo))
-> TxMeta -> Const (Maybe SlotNo) TxMeta)
-> Maybe SlotNo
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. IsLabel
"expiry"
((Maybe SlotNo -> Const (Maybe SlotNo) (Maybe SlotNo))
-> TxMeta -> Const (Maybe SlotNo) TxMeta)
(Maybe SlotNo -> Const (Maybe SlotNo) (Maybe SlotNo))
-> TxMeta -> Const (Maybe SlotNo) TxMeta
#expiry
, txMetadata :: Maybe TxMetadata
txMetadata = Tx -> Maybe TxMetadata
W.metadata Tx
tx
, txMetaScriptValidity :: Maybe Bool
txMetaScriptValidity = Tx -> Maybe TxScriptValidity
W.scriptValidity Tx
tx Maybe TxScriptValidity -> (TxScriptValidity -> Bool) -> Maybe Bool
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \case
TxScriptValidity
W.TxScriptValid -> Bool
True
TxScriptValidity
W.TxScriptInvalid -> Bool
False
}
mkTxMetaHistory :: W.WalletId -> [(W.Tx, W.TxMeta)] -> TxMetaHistory
mkTxMetaHistory :: WalletId -> [(Tx, TxMeta)] -> TxMetaHistory
mkTxMetaHistory WalletId
wid [(Tx, TxMeta)]
txs = Map TxId TxMeta -> TxMetaHistory
TxMetaHistory (Map TxId TxMeta -> TxMetaHistory)
-> Map TxId TxMeta -> TxMetaHistory
forall a b. (a -> b) -> a -> b
$
[(TxId, TxMeta)] -> Map TxId TxMeta
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
[ (Hash "Tx" -> TxId
TxId (Hash "Tx" -> TxId) -> Hash "Tx" -> TxId
forall a b. (a -> b) -> a -> b
$ Tx
tx Tx
-> ((Hash "Tx" -> Const (Hash "Tx") (Hash "Tx"))
-> Tx -> Const (Hash "Tx") Tx)
-> Hash "Tx"
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. IsLabel
"txId"
((Hash "Tx" -> Const (Hash "Tx") (Hash "Tx"))
-> Tx -> Const (Hash "Tx") Tx)
(Hash "Tx" -> Const (Hash "Tx") (Hash "Tx"))
-> Tx -> Const (Hash "Tx") Tx
#txId, WalletId -> Tx -> TxMeta -> TxMeta
mkTxMetaEntity WalletId
wid Tx
tx TxMeta
meta)
| (Tx
tx, TxMeta
meta) <- [(Tx, TxMeta)]
txs
]