Skip to content

Commit

Permalink
Add TxMeta type
Browse files Browse the repository at this point in the history
Remove comments

[101] Final polish of TxMeta type
  • Loading branch information
akegalj authored and paweljakubas committed Mar 26, 2019
1 parent 38ab655 commit bd6b33c
Showing 1 changed file with 31 additions and 0 deletions.
31 changes: 31 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,29 @@ instance Buildable TxOut where
instance Buildable (TxIn, TxOut) where
build (txin, txout) = build txin <> " ==> " <> build txout

data TxMeta = TxMeta
{ txId :: !(Hash "Tx")
, depth :: !(Quantity "block" Natural)
, status :: !TxStatus
, 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
{ getTimestamp :: UTCTime
} deriving (Show, Generic, Eq, Ord)

-- * Address

Expand Down

0 comments on commit bd6b33c

Please sign in to comment.