haskoin-wallet-0.4.2: Implementation of a Bitcoin SPV Wallet with BIP32 and multisig support.

Safe HaskellNone
LanguageHaskell98

Network.Haskoin.Wallet.Model

Documentation

data Account Source #

Constructors

Account 

Fields

Instances

Show Account Source # 
PersistEntity Account Source # 

Associated Types

type PersistEntityBackend Account :: *

data Key Account :: *

data EntityField Account a :: * #

data Unique Account :: * #

Methods

keyToValues :: Key Account -> [PersistValue]

keyFromValues :: [PersistValue] -> Either Text (Key Account)

persistIdField :: EntityField Account (Key Account)

entityDef :: Monad m => m Account -> EntityDef

persistFieldDef :: EntityField Account typ -> FieldDef

toPersistFields :: Account -> [SomePersistField]

fromPersistValues :: [PersistValue] -> Either Text Account

persistUniqueKeys :: Account -> [Unique Account]

persistUniqueToFieldNames :: Unique Account -> [(HaskellName, DBName)]

persistUniqueToValues :: Unique Account -> [PersistValue]

fieldLens :: EntityField Account field -> forall f. Functor f => (field -> f field) -> Entity Account -> f (Entity Account)

PersistField Account Source # 

Methods

toPersistValue :: Account -> PersistValue

fromPersistValue :: PersistValue -> Either Text Account

PersistFieldSql Account Source # 

Methods

sqlType :: Proxy * Account -> SqlType

ToBackendKey SqlBackend Account Source # 

Methods

toBackendKey :: Key Account -> BackendKey SqlBackend

fromBackendKey :: BackendKey SqlBackend -> Key Account

Eq (Key Account) Source # 

Methods

(==) :: Key Account -> Key Account -> Bool #

(/=) :: Key Account -> Key Account -> Bool #

Ord (Key Account) Source # 

Methods

compare :: Key Account -> Key Account -> Ordering #

(<) :: Key Account -> Key Account -> Bool #

(<=) :: Key Account -> Key Account -> Bool #

(>) :: Key Account -> Key Account -> Bool #

(>=) :: Key Account -> Key Account -> Bool #

max :: Key Account -> Key Account -> Key Account #

min :: Key Account -> Key Account -> Key Account #

Read (Key Account) Source # 
Show (Key Account) Source # 

Methods

showsPrec :: Int -> Key Account -> ShowS #

show :: Key Account -> String #

showList :: [Key Account] -> ShowS #

ToJSON (Key Account) Source # 

Methods

toJSON :: Key Account -> Value

toEncoding :: Key Account -> Encoding

toJSONList :: [Key Account] -> Value

toEncodingList :: [Key Account] -> Encoding

FromJSON (Key Account) Source # 

Methods

parseJSON :: Value -> Parser (Key Account)

parseJSONList :: Value -> Parser [Key Account]

PersistField (Key Account) Source # 

Methods

toPersistValue :: Key Account -> PersistValue

fromPersistValue :: PersistValue -> Either Text (Key Account)

ToHttpApiData (Key Account) Source # 

Methods

toUrlPiece :: Key Account -> Text

toEncodedUrlPiece :: Key Account -> Builder

toHeader :: Key Account -> ByteString

toQueryParam :: Key Account -> Text

PersistFieldSql (Key Account) Source # 

Methods

sqlType :: Proxy * (Key Account) -> SqlType

PathPiece (Key Account) Source # 

Methods

fromPathPiece :: Text -> Maybe (Key Account)

toPathPiece :: Key Account -> Text

FromHttpApiData (Key Account) Source # 

Methods

parseUrlPiece :: Text -> Either Text (Key Account)

parseHeader :: ByteString -> Either Text (Key Account)

parseQueryParam :: Text -> Either Text (Key Account)

type PersistEntityBackend Account Source # 
type PersistEntityBackend Account = SqlBackend
data Key Account Source # 
data Key Account = AccountKey {}
data EntityField Account Source # 
data Unique Account Source # 

data WalletAddr Source #

Constructors

WalletAddr 

Fields

Instances

Show WalletAddr Source # 
PersistEntity WalletAddr Source # 

Associated Types

type PersistEntityBackend WalletAddr :: *

data Key WalletAddr :: *

data EntityField WalletAddr a :: * #

data Unique WalletAddr :: * #

Methods

keyToValues :: Key WalletAddr -> [PersistValue]

keyFromValues :: [PersistValue] -> Either Text (Key WalletAddr)

persistIdField :: EntityField WalletAddr (Key WalletAddr)

entityDef :: Monad m => m WalletAddr -> EntityDef

persistFieldDef :: EntityField WalletAddr typ -> FieldDef

toPersistFields :: WalletAddr -> [SomePersistField]

fromPersistValues :: [PersistValue] -> Either Text WalletAddr

persistUniqueKeys :: WalletAddr -> [Unique WalletAddr]

persistUniqueToFieldNames :: Unique WalletAddr -> [(HaskellName, DBName)]

persistUniqueToValues :: Unique WalletAddr -> [PersistValue]

fieldLens :: EntityField WalletAddr field -> forall f. Functor f => (field -> f field) -> Entity WalletAddr -> f (Entity WalletAddr)

PersistField WalletAddr Source # 

Methods

toPersistValue :: WalletAddr -> PersistValue

fromPersistValue :: PersistValue -> Either Text WalletAddr

PersistFieldSql WalletAddr Source # 

Methods

sqlType :: Proxy * WalletAddr -> SqlType

ToBackendKey SqlBackend WalletAddr Source # 

Methods

toBackendKey :: Key WalletAddr -> BackendKey SqlBackend

fromBackendKey :: BackendKey SqlBackend -> Key WalletAddr

Eq (Key WalletAddr) Source # 

Methods

(==) :: Key WalletAddr -> Key WalletAddr -> Bool #

(/=) :: Key WalletAddr -> Key WalletAddr -> Bool #

Ord (Key WalletAddr) Source # 

Methods

compare :: Key WalletAddr -> Key WalletAddr -> Ordering #

(<) :: Key WalletAddr -> Key WalletAddr -> Bool #

(<=) :: Key WalletAddr -> Key WalletAddr -> Bool #

(>) :: Key WalletAddr -> Key WalletAddr -> Bool #

(>=) :: Key WalletAddr -> Key WalletAddr -> Bool #

max :: Key WalletAddr -> Key WalletAddr -> Key WalletAddr #

min :: Key WalletAddr -> Key WalletAddr -> Key WalletAddr #

Read (Key WalletAddr) Source # 
Show (Key WalletAddr) Source # 

Methods

showsPrec :: Int -> Key WalletAddr -> ShowS #

show :: Key WalletAddr -> String #

showList :: [Key WalletAddr] -> ShowS #

ToJSON (Key WalletAddr) Source # 

Methods

toJSON :: Key WalletAddr -> Value

toEncoding :: Key WalletAddr -> Encoding

toJSONList :: [Key WalletAddr] -> Value

toEncodingList :: [Key WalletAddr] -> Encoding

FromJSON (Key WalletAddr) Source # 

Methods

parseJSON :: Value -> Parser (Key WalletAddr)

parseJSONList :: Value -> Parser [Key WalletAddr]

PersistField (Key WalletAddr) Source # 

Methods

toPersistValue :: Key WalletAddr -> PersistValue

fromPersistValue :: PersistValue -> Either Text (Key WalletAddr)

ToHttpApiData (Key WalletAddr) Source # 
PersistFieldSql (Key WalletAddr) Source # 

Methods

sqlType :: Proxy * (Key WalletAddr) -> SqlType

PathPiece (Key WalletAddr) Source # 

Methods

fromPathPiece :: Text -> Maybe (Key WalletAddr)

toPathPiece :: Key WalletAddr -> Text

FromHttpApiData (Key WalletAddr) Source # 

Methods

parseUrlPiece :: Text -> Either Text (Key WalletAddr)

parseHeader :: ByteString -> Either Text (Key WalletAddr)

parseQueryParam :: Text -> Either Text (Key WalletAddr)

type PersistEntityBackend WalletAddr Source # 
type PersistEntityBackend WalletAddr = SqlBackend
data Key WalletAddr Source # 
data Key WalletAddr = WalletAddrKey' {}
data EntityField WalletAddr Source # 
data Unique WalletAddr Source # 
data Unique WalletAddr

data WalletState Source #

Instances

Show WalletState Source # 
PersistEntity WalletState Source # 

Associated Types

type PersistEntityBackend WalletState :: *

data Key WalletState :: *

data EntityField WalletState a :: * #

data Unique WalletState :: * #

Methods

keyToValues :: Key WalletState -> [PersistValue]

keyFromValues :: [PersistValue] -> Either Text (Key WalletState)

persistIdField :: EntityField WalletState (Key WalletState)

entityDef :: Monad m => m WalletState -> EntityDef

persistFieldDef :: EntityField WalletState typ -> FieldDef

toPersistFields :: WalletState -> [SomePersistField]

fromPersistValues :: [PersistValue] -> Either Text WalletState

persistUniqueKeys :: WalletState -> [Unique WalletState]

persistUniqueToFieldNames :: Unique WalletState -> [(HaskellName, DBName)]

persistUniqueToValues :: Unique WalletState -> [PersistValue]

fieldLens :: EntityField WalletState field -> forall f. Functor f => (field -> f field) -> Entity WalletState -> f (Entity WalletState)

PersistField WalletState Source # 

Methods

toPersistValue :: WalletState -> PersistValue

fromPersistValue :: PersistValue -> Either Text WalletState

PersistFieldSql WalletState Source # 

Methods

sqlType :: Proxy * WalletState -> SqlType

ToBackendKey SqlBackend WalletState Source # 

Methods

toBackendKey :: Key WalletState -> BackendKey SqlBackend

fromBackendKey :: BackendKey SqlBackend -> Key WalletState

Eq (Key WalletState) Source # 

Methods

(==) :: Key WalletState -> Key WalletState -> Bool #

(/=) :: Key WalletState -> Key WalletState -> Bool #

Ord (Key WalletState) Source # 

Methods

compare :: Key WalletState -> Key WalletState -> Ordering #

(<) :: Key WalletState -> Key WalletState -> Bool #

(<=) :: Key WalletState -> Key WalletState -> Bool #

(>) :: Key WalletState -> Key WalletState -> Bool #

(>=) :: Key WalletState -> Key WalletState -> Bool #

max :: Key WalletState -> Key WalletState -> Key WalletState #

min :: Key WalletState -> Key WalletState -> Key WalletState #

Read (Key WalletState) Source # 
Show (Key WalletState) Source # 

Methods

showsPrec :: Int -> Key WalletState -> ShowS #

show :: Key WalletState -> String #

showList :: [Key WalletState] -> ShowS #

ToJSON (Key WalletState) Source # 

Methods

toJSON :: Key WalletState -> Value

toEncoding :: Key WalletState -> Encoding

toJSONList :: [Key WalletState] -> Value

toEncodingList :: [Key WalletState] -> Encoding

FromJSON (Key WalletState) Source # 

Methods

parseJSON :: Value -> Parser (Key WalletState)

parseJSONList :: Value -> Parser [Key WalletState]

PersistField (Key WalletState) Source # 

Methods

toPersistValue :: Key WalletState -> PersistValue

fromPersistValue :: PersistValue -> Either Text (Key WalletState)

ToHttpApiData (Key WalletState) Source # 
PersistFieldSql (Key WalletState) Source # 

Methods

sqlType :: Proxy * (Key WalletState) -> SqlType

PathPiece (Key WalletState) Source # 

Methods

fromPathPiece :: Text -> Maybe (Key WalletState)

toPathPiece :: Key WalletState -> Text

FromHttpApiData (Key WalletState) Source # 

Methods

parseUrlPiece :: Text -> Either Text (Key WalletState)

parseHeader :: ByteString -> Either Text (Key WalletState)

parseQueryParam :: Text -> Either Text (Key WalletState)

type PersistEntityBackend WalletState Source # 
type PersistEntityBackend WalletState = SqlBackend
data Key WalletState Source # 
data Key WalletState = WalletStateKey {}
data EntityField WalletState Source # 
data Unique WalletState Source # 

data WalletCoin Source #

Instances

Show WalletCoin Source # 
PersistEntity WalletCoin Source # 

Associated Types

type PersistEntityBackend WalletCoin :: *

data Key WalletCoin :: *

data EntityField WalletCoin a :: * #

data Unique WalletCoin :: * #

Methods

keyToValues :: Key WalletCoin -> [PersistValue]

keyFromValues :: [PersistValue] -> Either Text (Key WalletCoin)

persistIdField :: EntityField WalletCoin (Key WalletCoin)

entityDef :: Monad m => m WalletCoin -> EntityDef

persistFieldDef :: EntityField WalletCoin typ -> FieldDef

toPersistFields :: WalletCoin -> [SomePersistField]

fromPersistValues :: [PersistValue] -> Either Text WalletCoin

persistUniqueKeys :: WalletCoin -> [Unique WalletCoin]

persistUniqueToFieldNames :: Unique WalletCoin -> [(HaskellName, DBName)]

persistUniqueToValues :: Unique WalletCoin -> [PersistValue]

fieldLens :: EntityField WalletCoin field -> forall f. Functor f => (field -> f field) -> Entity WalletCoin -> f (Entity WalletCoin)

PersistField WalletCoin Source # 

Methods

toPersistValue :: WalletCoin -> PersistValue

fromPersistValue :: PersistValue -> Either Text WalletCoin

PersistFieldSql WalletCoin Source # 

Methods

sqlType :: Proxy * WalletCoin -> SqlType

ToBackendKey SqlBackend WalletCoin Source # 

Methods

toBackendKey :: Key WalletCoin -> BackendKey SqlBackend

fromBackendKey :: BackendKey SqlBackend -> Key WalletCoin

Eq (Key WalletCoin) Source # 

Methods

(==) :: Key WalletCoin -> Key WalletCoin -> Bool #

(/=) :: Key WalletCoin -> Key WalletCoin -> Bool #

Ord (Key WalletCoin) Source # 

Methods

compare :: Key WalletCoin -> Key WalletCoin -> Ordering #

(<) :: Key WalletCoin -> Key WalletCoin -> Bool #

(<=) :: Key WalletCoin -> Key WalletCoin -> Bool #

(>) :: Key WalletCoin -> Key WalletCoin -> Bool #

(>=) :: Key WalletCoin -> Key WalletCoin -> Bool #

max :: Key WalletCoin -> Key WalletCoin -> Key WalletCoin #

min :: Key WalletCoin -> Key WalletCoin -> Key WalletCoin #

Read (Key WalletCoin) Source # 
Show (Key WalletCoin) Source # 

Methods

showsPrec :: Int -> Key WalletCoin -> ShowS #

show :: Key WalletCoin -> String #

showList :: [Key WalletCoin] -> ShowS #

ToJSON (Key WalletCoin) Source # 

Methods

toJSON :: Key WalletCoin -> Value

toEncoding :: Key WalletCoin -> Encoding

toJSONList :: [Key WalletCoin] -> Value

toEncodingList :: [Key WalletCoin] -> Encoding

FromJSON (Key WalletCoin) Source # 

Methods

parseJSON :: Value -> Parser (Key WalletCoin)

parseJSONList :: Value -> Parser [Key WalletCoin]

PersistField (Key WalletCoin) Source # 

Methods

toPersistValue :: Key WalletCoin -> PersistValue

fromPersistValue :: PersistValue -> Either Text (Key WalletCoin)

ToHttpApiData (Key WalletCoin) Source # 
PersistFieldSql (Key WalletCoin) Source # 

Methods

sqlType :: Proxy * (Key WalletCoin) -> SqlType

PathPiece (Key WalletCoin) Source # 

Methods

fromPathPiece :: Text -> Maybe (Key WalletCoin)

toPathPiece :: Key WalletCoin -> Text

FromHttpApiData (Key WalletCoin) Source # 

Methods

parseUrlPiece :: Text -> Either Text (Key WalletCoin)

parseHeader :: ByteString -> Either Text (Key WalletCoin)

parseQueryParam :: Text -> Either Text (Key WalletCoin)

type PersistEntityBackend WalletCoin Source # 
type PersistEntityBackend WalletCoin = SqlBackend
data Key WalletCoin Source # 
data Key WalletCoin = WalletCoinKey {}
data EntityField WalletCoin Source # 
data Unique WalletCoin Source # 

data SpentCoin Source #

Instances

Show SpentCoin Source # 
PersistEntity SpentCoin Source # 

Associated Types

type PersistEntityBackend SpentCoin :: *

data Key SpentCoin :: *

data EntityField SpentCoin a :: * #

data Unique SpentCoin :: * #

Methods

keyToValues :: Key SpentCoin -> [PersistValue]

keyFromValues :: [PersistValue] -> Either Text (Key SpentCoin)

persistIdField :: EntityField SpentCoin (Key SpentCoin)

entityDef :: Monad m => m SpentCoin -> EntityDef

persistFieldDef :: EntityField SpentCoin typ -> FieldDef

toPersistFields :: SpentCoin -> [SomePersistField]

fromPersistValues :: [PersistValue] -> Either Text SpentCoin

persistUniqueKeys :: SpentCoin -> [Unique SpentCoin]

persistUniqueToFieldNames :: Unique SpentCoin -> [(HaskellName, DBName)]

persistUniqueToValues :: Unique SpentCoin -> [PersistValue]

fieldLens :: EntityField SpentCoin field -> forall f. Functor f => (field -> f field) -> Entity SpentCoin -> f (Entity SpentCoin)

PersistField SpentCoin Source # 

Methods

toPersistValue :: SpentCoin -> PersistValue

fromPersistValue :: PersistValue -> Either Text SpentCoin

PersistFieldSql SpentCoin Source # 

Methods

sqlType :: Proxy * SpentCoin -> SqlType

ToBackendKey SqlBackend SpentCoin Source # 

Methods

toBackendKey :: Key SpentCoin -> BackendKey SqlBackend

fromBackendKey :: BackendKey SqlBackend -> Key SpentCoin

Eq (Key SpentCoin) Source # 

Methods

(==) :: Key SpentCoin -> Key SpentCoin -> Bool #

(/=) :: Key SpentCoin -> Key SpentCoin -> Bool #

Ord (Key SpentCoin) Source # 

Methods

compare :: Key SpentCoin -> Key SpentCoin -> Ordering #

(<) :: Key SpentCoin -> Key SpentCoin -> Bool #

(<=) :: Key SpentCoin -> Key SpentCoin -> Bool #

(>) :: Key SpentCoin -> Key SpentCoin -> Bool #

(>=) :: Key SpentCoin -> Key SpentCoin -> Bool #

max :: Key SpentCoin -> Key SpentCoin -> Key SpentCoin #

min :: Key SpentCoin -> Key SpentCoin -> Key SpentCoin #

Read (Key SpentCoin) Source # 
Show (Key SpentCoin) Source # 

Methods

showsPrec :: Int -> Key SpentCoin -> ShowS #

show :: Key SpentCoin -> String #

showList :: [Key SpentCoin] -> ShowS #

ToJSON (Key SpentCoin) Source # 

Methods

toJSON :: Key SpentCoin -> Value

toEncoding :: Key SpentCoin -> Encoding

toJSONList :: [Key SpentCoin] -> Value

toEncodingList :: [Key SpentCoin] -> Encoding

FromJSON (Key SpentCoin) Source # 

Methods

parseJSON :: Value -> Parser (Key SpentCoin)

parseJSONList :: Value -> Parser [Key SpentCoin]

PersistField (Key SpentCoin) Source # 

Methods

toPersistValue :: Key SpentCoin -> PersistValue

fromPersistValue :: PersistValue -> Either Text (Key SpentCoin)

ToHttpApiData (Key SpentCoin) Source # 
PersistFieldSql (Key SpentCoin) Source # 

Methods

sqlType :: Proxy * (Key SpentCoin) -> SqlType

PathPiece (Key SpentCoin) Source # 

Methods

fromPathPiece :: Text -> Maybe (Key SpentCoin)

toPathPiece :: Key SpentCoin -> Text

FromHttpApiData (Key SpentCoin) Source # 

Methods

parseUrlPiece :: Text -> Either Text (Key SpentCoin)

parseHeader :: ByteString -> Either Text (Key SpentCoin)

parseQueryParam :: Text -> Either Text (Key SpentCoin)

type PersistEntityBackend SpentCoin Source # 
type PersistEntityBackend SpentCoin = SqlBackend
data Key SpentCoin Source # 
data Key SpentCoin = SpentCoinKey {}
data EntityField SpentCoin Source # 
data Unique SpentCoin Source # 

data WalletTx Source #

Instances

Show WalletTx Source # 
PersistEntity WalletTx Source # 

Associated Types

type PersistEntityBackend WalletTx :: *

data Key WalletTx :: *

data EntityField WalletTx a :: * #

data Unique WalletTx :: * #

Methods

keyToValues :: Key WalletTx -> [PersistValue]

keyFromValues :: [PersistValue] -> Either Text (Key WalletTx)

persistIdField :: EntityField WalletTx (Key WalletTx)

entityDef :: Monad m => m WalletTx -> EntityDef

persistFieldDef :: EntityField WalletTx typ -> FieldDef

toPersistFields :: WalletTx -> [SomePersistField]

fromPersistValues :: [PersistValue] -> Either Text WalletTx

persistUniqueKeys :: WalletTx -> [Unique WalletTx]

persistUniqueToFieldNames :: Unique WalletTx -> [(HaskellName, DBName)]

persistUniqueToValues :: Unique WalletTx -> [PersistValue]

fieldLens :: EntityField WalletTx field -> forall f. Functor f => (field -> f field) -> Entity WalletTx -> f (Entity WalletTx)

PersistField WalletTx Source # 

Methods

toPersistValue :: WalletTx -> PersistValue

fromPersistValue :: PersistValue -> Either Text WalletTx

PersistFieldSql WalletTx Source # 

Methods

sqlType :: Proxy * WalletTx -> SqlType

ToBackendKey SqlBackend WalletTx Source # 

Methods

toBackendKey :: Key WalletTx -> BackendKey SqlBackend

fromBackendKey :: BackendKey SqlBackend -> Key WalletTx

Eq (Key WalletTx) Source # 

Methods

(==) :: Key WalletTx -> Key WalletTx -> Bool #

(/=) :: Key WalletTx -> Key WalletTx -> Bool #

Ord (Key WalletTx) Source # 

Methods

compare :: Key WalletTx -> Key WalletTx -> Ordering #

(<) :: Key WalletTx -> Key WalletTx -> Bool #

(<=) :: Key WalletTx -> Key WalletTx -> Bool #

(>) :: Key WalletTx -> Key WalletTx -> Bool #

(>=) :: Key WalletTx -> Key WalletTx -> Bool #

max :: Key WalletTx -> Key WalletTx -> Key WalletTx #

min :: Key WalletTx -> Key WalletTx -> Key WalletTx #

Read (Key WalletTx) Source # 
Show (Key WalletTx) Source # 

Methods

showsPrec :: Int -> Key WalletTx -> ShowS #

show :: Key WalletTx -> String #

showList :: [Key WalletTx] -> ShowS #

ToJSON (Key WalletTx) Source # 

Methods

toJSON :: Key WalletTx -> Value

toEncoding :: Key WalletTx -> Encoding

toJSONList :: [Key WalletTx] -> Value

toEncodingList :: [Key WalletTx] -> Encoding

FromJSON (Key WalletTx) Source # 

Methods

parseJSON :: Value -> Parser (Key WalletTx)

parseJSONList :: Value -> Parser [Key WalletTx]

PersistField (Key WalletTx) Source # 

Methods

toPersistValue :: Key WalletTx -> PersistValue

fromPersistValue :: PersistValue -> Either Text (Key WalletTx)

ToHttpApiData (Key WalletTx) Source # 
PersistFieldSql (Key WalletTx) Source # 

Methods

sqlType :: Proxy * (Key WalletTx) -> SqlType

PathPiece (Key WalletTx) Source # 

Methods

fromPathPiece :: Text -> Maybe (Key WalletTx)

toPathPiece :: Key WalletTx -> Text

FromHttpApiData (Key WalletTx) Source # 

Methods

parseUrlPiece :: Text -> Either Text (Key WalletTx)

parseHeader :: ByteString -> Either Text (Key WalletTx)

parseQueryParam :: Text -> Either Text (Key WalletTx)

type PersistEntityBackend WalletTx Source # 
type PersistEntityBackend WalletTx = SqlBackend
data Key WalletTx Source # 
data Key WalletTx = WalletTxKey {}
data EntityField WalletTx Source # 
data Unique WalletTx Source # 
data Unique WalletTx

data family EntityField record a :: * #

Instances

data EntityField NodeBlock 
data EntityField NodeBlock where
data EntityField WalletState # 
data EntityField SpentCoin # 
data EntityField WalletCoin # 
data EntityField WalletTx # 
data EntityField WalletAddr # 
data EntityField Account # 

data family Unique record :: * #

Instances

migrateWallet :: Migration Source #

toJsonCoin Source #

Arguments

:: WalletCoin 
-> Maybe JsonTx

Coin’s transaction

-> Maybe JsonAddr

Coin’s address

-> Maybe JsonTx

Coin’s spending transaction

-> JsonCoin 

toJsonTx Source #

Arguments

:: AccountName 
-> Maybe (BlockHash, BlockHeight)

Current best block

-> WalletTx 
-> JsonTx