Skip to content

Commit

Permalink
Add TxMeta type
Browse files Browse the repository at this point in the history
  • Loading branch information
akegalj committed Mar 22, 2019
1 parent 15cfea7 commit 7672449
Showing 1 changed file with 41 additions and 0 deletions.
41 changes: 41 additions & 0 deletions src/Cardano/Wallet/Primitive/Types.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE RankNTypes #-}
Expand Down Expand Up @@ -29,6 +30,7 @@ module Cardano.Wallet.Primitive.Types
, Tx(..)
, TxIn(..)
, TxOut(..)
, TxMeta(..)
, txIns
, updatePending

Expand Down Expand Up @@ -74,8 +76,12 @@ import Data.ByteString.Base58
( bitcoinAlphabet, encodeBase58 )
import Data.Map.Strict
( Map )
import Data.Quantity
( Quantity (..) )
import Data.Set
( Set )
import Data.Time
( UTCTime )
import Data.Word
( Word16, Word32, Word64 )
import Fmt
Expand All @@ -93,6 +99,8 @@ import GHC.Generics
( Generic )
import GHC.TypeLits
( Symbol )
import Numeric.Natural
( Natural )

import qualified Data.Map.Strict as Map
import qualified Data.Set as Set
Expand Down Expand Up @@ -212,6 +220,39 @@ instance Buildable TxOut where
instance Buildable (TxIn, TxOut) where
build (txin, txout) = build txin <> " ==> " <> build txout

data TxMeta = TxMeta
{ metaId :: !(Hash "Tx")
-- FIXME: we might want to go for something more optimized than natural,
-- like Word64 ?
, depth :: !(Quantity "block" Natural)
, status :: !TxStatus
-- FIXME: should we use Quantity "lovelace" Natural ?
-- I wonder could we use somethine like proposed instead of Coin in wallet
-- part alltogether. Node/core bits would still work optimally with
-- Coin/Word64
-- but wallet bits could go a bit more abstract (and less optimized)?
, amount :: !Coin
, direction :: !Direction
, timestamp :: !Timestamp
, slotId :: !SlotId
} deriving (Show, Eq, Generic)

data TxStatus
= Pending
| InLedger
| Invalidated
deriving (Show, Eq, Generic)

data Direction
= Outgoing
| Incoming
deriving (Show, Eq, Generic)

newtype Timestamp = Timestamp
-- NOTE: We could have gone for Microsecond from Data.Time.Units, but
-- it seems like an overkill for now
{ getTimestamp :: UTCTime
} deriving (Show, Generic, Eq, Ord)

-- * Address

Expand Down

0 comments on commit 7672449

Please sign in to comment.