lnd-client-0.1.0.0: Lightning Network Daemon (LND) client library for Haskell

Safe HaskellNone
LanguageHaskell2010

LndClient.Data.Newtype

Documentation

newtype AddIndex Source #

Constructors

AddIndex Word64 
Instances
Eq AddIndex Source # 
Instance details

Defined in LndClient.Data.Newtype

Ord AddIndex Source # 
Instance details

Defined in LndClient.Data.Newtype

Show AddIndex Source # 
Instance details

Defined in LndClient.Data.Newtype

PersistField AddIndex Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

toPersistValue :: AddIndex -> PersistValue

fromPersistValue :: PersistValue -> Either Text AddIndex

PersistFieldSql AddIndex Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

sqlType :: Proxy AddIndex -> SqlType

FromGrpc AddIndex Word64 Source # 
Instance details

Defined in LndClient.Data.Newtype

ToGrpc AddIndex Word64 Source # 
Instance details

Defined in LndClient.Data.Newtype

newtype PaymentRequest Source #

Constructors

PaymentRequest Text 
Instances
Eq PaymentRequest Source # 
Instance details

Defined in LndClient.Data.Newtype

Show PaymentRequest Source # 
Instance details

Defined in LndClient.Data.Newtype

PersistField PaymentRequest Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

toPersistValue :: PaymentRequest -> PersistValue

fromPersistValue :: PersistValue -> Either Text PaymentRequest

PersistFieldSql PaymentRequest Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

sqlType :: Proxy PaymentRequest -> SqlType

ToText PaymentRequest Source # 
Instance details

Defined in LndClient.Data.Newtype

FromGrpc PaymentRequest Text Source # 
Instance details

Defined in LndClient.Data.Newtype

FromGrpc PaymentRequest AddHoldInvoiceResp Source # 
Instance details

Defined in LndClient.Data.Newtype

ToGrpc PaymentRequest Text Source # 
Instance details

Defined in LndClient.Data.Newtype

ToGrpc PaymentRequest PayReqString Source # 
Instance details

Defined in LndClient.Data.Newtype

newtype RHash Source #

Constructors

RHash ByteString 
Instances
Eq RHash Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

(==) :: RHash -> RHash -> Bool #

(/=) :: RHash -> RHash -> Bool #

Ord RHash Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

compare :: RHash -> RHash -> Ordering #

(<) :: RHash -> RHash -> Bool #

(<=) :: RHash -> RHash -> Bool #

(>) :: RHash -> RHash -> Bool #

(>=) :: RHash -> RHash -> Bool #

max :: RHash -> RHash -> RHash #

min :: RHash -> RHash -> RHash #

Show RHash Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

showsPrec :: Int -> RHash -> ShowS #

show :: RHash -> String #

showList :: [RHash] -> ShowS #

PersistField RHash Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

toPersistValue :: RHash -> PersistValue

fromPersistValue :: PersistValue -> Either Text RHash

PersistFieldSql RHash Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

sqlType :: Proxy RHash -> SqlType

FromGrpc RHash ByteString Source # 
Instance details

Defined in LndClient.Data.Newtype

FromGrpc RHash Text Source # 
Instance details

Defined in LndClient.Data.Newtype

ToGrpc RHash ByteString Source # 
Instance details

Defined in LndClient.Data.Newtype

ToGrpc RHash PaymentHash Source # 
Instance details

Defined in LndClient.Data.Newtype

ToGrpc RHash SubscribeSingleInvoiceRequest Source # 
Instance details

Defined in LndClient.Data.Newtype

ToGrpc RHash CancelInvoiceMsg Source # 
Instance details

Defined in LndClient.Data.Newtype

newtype RPreimage Source #

Constructors

RPreimage ByteString 
Instances
Eq RPreimage Source # 
Instance details

Defined in LndClient.Data.Newtype

Ord RPreimage Source # 
Instance details

Defined in LndClient.Data.Newtype

Show RPreimage Source # 
Instance details

Defined in LndClient.Data.Newtype

PersistField RPreimage Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

toPersistValue :: RPreimage -> PersistValue

fromPersistValue :: PersistValue -> Either Text RPreimage

PersistFieldSql RPreimage Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

sqlType :: Proxy RPreimage -> SqlType

FromGrpc RPreimage ByteString Source # 
Instance details

Defined in LndClient.Data.Newtype

FromGrpc RPreimage Text Source # 
Instance details

Defined in LndClient.Data.Newtype

ToGrpc RPreimage ByteString Source # 
Instance details

Defined in LndClient.Data.Newtype

ToGrpc RPreimage SettleInvoiceMsg Source # 
Instance details

Defined in LndClient.Data.Newtype

newtype MSat Source #

Constructors

MSat Word64 
Instances
Eq MSat Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

(==) :: MSat -> MSat -> Bool #

(/=) :: MSat -> MSat -> Bool #

Num MSat Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

(+) :: MSat -> MSat -> MSat #

(-) :: MSat -> MSat -> MSat #

(*) :: MSat -> MSat -> MSat #

negate :: MSat -> MSat #

abs :: MSat -> MSat #

signum :: MSat -> MSat #

fromInteger :: Integer -> MSat #

Ord MSat Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

compare :: MSat -> MSat -> Ordering #

(<) :: MSat -> MSat -> Bool #

(<=) :: MSat -> MSat -> Bool #

(>) :: MSat -> MSat -> Bool #

(>=) :: MSat -> MSat -> Bool #

max :: MSat -> MSat -> MSat #

min :: MSat -> MSat -> MSat #

Show MSat Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

showsPrec :: Int -> MSat -> ShowS #

show :: MSat -> String #

showList :: [MSat] -> ShowS #

FromJSON MSat Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

parseJSON :: Value -> Parser MSat #

parseJSONList :: Value -> Parser [MSat] #

PersistField MSat Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

toPersistValue :: MSat -> PersistValue

fromPersistValue :: PersistValue -> Either Text MSat

PersistFieldSql MSat Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

sqlType :: Proxy MSat -> SqlType

FromGrpc MSat Int64 Source # 
Instance details

Defined in LndClient.Data.Newtype

FromGrpc MSat Word64 Source # 
Instance details

Defined in LndClient.Data.Newtype

ToGrpc MSat Int64 Source # 
Instance details

Defined in LndClient.Data.Newtype

newtype Sat Source #

Constructors

Sat Word64 
Instances
Eq Sat Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

(==) :: Sat -> Sat -> Bool #

(/=) :: Sat -> Sat -> Bool #

Num Sat Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

(+) :: Sat -> Sat -> Sat #

(-) :: Sat -> Sat -> Sat #

(*) :: Sat -> Sat -> Sat #

negate :: Sat -> Sat #

abs :: Sat -> Sat #

signum :: Sat -> Sat #

fromInteger :: Integer -> Sat #

Ord Sat Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

compare :: Sat -> Sat -> Ordering #

(<) :: Sat -> Sat -> Bool #

(<=) :: Sat -> Sat -> Bool #

(>) :: Sat -> Sat -> Bool #

(>=) :: Sat -> Sat -> Bool #

max :: Sat -> Sat -> Sat #

min :: Sat -> Sat -> Sat #

Show Sat Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

showsPrec :: Int -> Sat -> ShowS #

show :: Sat -> String #

showList :: [Sat] -> ShowS #

FromJSON Sat Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

parseJSON :: Value -> Parser Sat #

parseJSONList :: Value -> Parser [Sat] #

FromGrpc Sat Int64 Source # 
Instance details

Defined in LndClient.Data.Newtype

ToGrpc Sat Int64 Source # 
Instance details

Defined in LndClient.Data.Newtype

newtype Seconds Source #

Constructors

Seconds Word64 
Instances
Eq Seconds Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

(==) :: Seconds -> Seconds -> Bool #

(/=) :: Seconds -> Seconds -> Bool #

Show Seconds Source # 
Instance details

Defined in LndClient.Data.Newtype

FromJSON Seconds Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

parseJSON :: Value -> Parser Seconds #

parseJSONList :: Value -> Parser [Seconds] #

PersistField Seconds Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

toPersistValue :: Seconds -> PersistValue

fromPersistValue :: PersistValue -> Either Text Seconds

PersistFieldSql Seconds Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

sqlType :: Proxy Seconds -> SqlType

FromGrpc Seconds Int64 Source # 
Instance details

Defined in LndClient.Data.Newtype

ToGrpc Seconds Int64 Source # 
Instance details

Defined in LndClient.Data.Newtype

newtype NodePubKey Source #

Constructors

NodePubKey ByteString 
Instances
Eq NodePubKey Source # 
Instance details

Defined in LndClient.Data.Newtype

Ord NodePubKey Source # 
Instance details

Defined in LndClient.Data.Newtype

Read NodePubKey Source # 
Instance details

Defined in LndClient.Data.Newtype

Show NodePubKey Source # 
Instance details

Defined in LndClient.Data.Newtype

PersistField NodePubKey Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

toPersistValue :: NodePubKey -> PersistValue

fromPersistValue :: PersistValue -> Either Text NodePubKey

PersistFieldSql NodePubKey Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

sqlType :: Proxy NodePubKey -> SqlType

FromGrpc NodePubKey ByteString Source # 
Instance details

Defined in LndClient.Data.Newtype

FromGrpc NodePubKey Text Source # 
Instance details

Defined in LndClient.Data.Newtype

ToGrpc NodePubKey ByteString Source # 
Instance details

Defined in LndClient.Data.Newtype

ToGrpc NodePubKey Text Source # 
Instance details

Defined in LndClient.Data.Newtype

newtype NodeLocation Source #

Constructors

NodeLocation Text 
Instances
Eq NodeLocation Source # 
Instance details

Defined in LndClient.Data.Newtype

Ord NodeLocation Source # 
Instance details

Defined in LndClient.Data.Newtype

Read NodeLocation Source # 
Instance details

Defined in LndClient.Data.Newtype

Show NodeLocation Source # 
Instance details

Defined in LndClient.Data.Newtype

PersistField NodeLocation Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

toPersistValue :: NodeLocation -> PersistValue

fromPersistValue :: PersistValue -> Either Text NodeLocation

PersistFieldSql NodeLocation Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

sqlType :: Proxy NodeLocation -> SqlType

FromGrpc NodeLocation Text Source # 
Instance details

Defined in LndClient.Data.Newtype

ToGrpc NodeLocation Text Source # 
Instance details

Defined in LndClient.Data.Newtype

newtype TxId (a :: TxKind) Source #

Constructors

TxId ByteString 
Instances
Eq (TxId a) Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

(==) :: TxId a -> TxId a -> Bool #

(/=) :: TxId a -> TxId a -> Bool #

Ord (TxId a) Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

compare :: TxId a -> TxId a -> Ordering #

(<) :: TxId a -> TxId a -> Bool #

(<=) :: TxId a -> TxId a -> Bool #

(>) :: TxId a -> TxId a -> Bool #

(>=) :: TxId a -> TxId a -> Bool #

max :: TxId a -> TxId a -> TxId a #

min :: TxId a -> TxId a -> TxId a #

Show (TxId a) Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

showsPrec :: Int -> TxId a -> ShowS #

show :: TxId a -> String #

showList :: [TxId a] -> ShowS #

PersistField (TxId a) Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

toPersistValue :: TxId a -> PersistValue

fromPersistValue :: PersistValue -> Either Text (TxId a)

PersistFieldSql (TxId a) Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

sqlType :: Proxy (TxId a) -> SqlType

FromGrpc (TxId a) Text Source # 
Instance details

Defined in LndClient.Data.Newtype

FromGrpc (TxId a) ByteString Source # 
Instance details

Defined in LndClient.Data.Newtype

ToGrpc (TxId a) ByteString Source # 
Instance details

Defined in LndClient.Data.Newtype

newtype Vout (a :: TxKind) Source #

Constructors

Vout Word32 
Instances
Eq (Vout a) Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

(==) :: Vout a -> Vout a -> Bool #

(/=) :: Vout a -> Vout a -> Bool #

Ord (Vout a) Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

compare :: Vout a -> Vout a -> Ordering #

(<) :: Vout a -> Vout a -> Bool #

(<=) :: Vout a -> Vout a -> Bool #

(>) :: Vout a -> Vout a -> Bool #

(>=) :: Vout a -> Vout a -> Bool #

max :: Vout a -> Vout a -> Vout a #

min :: Vout a -> Vout a -> Vout a #

Read (Vout a) Source # 
Instance details

Defined in LndClient.Data.Newtype

Show (Vout a) Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

showsPrec :: Int -> Vout a -> ShowS #

show :: Vout a -> String #

showList :: [Vout a] -> ShowS #

PersistField (Vout a) Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

toPersistValue :: Vout a -> PersistValue

fromPersistValue :: PersistValue -> Either Text (Vout a)

PersistFieldSql (Vout a) Source # 
Instance details

Defined in LndClient.Data.Newtype

Methods

sqlType :: Proxy (Vout a) -> SqlType

FromGrpc (Vout a) Word32 Source # 
Instance details

Defined in LndClient.Data.Newtype

ToGrpc (Vout a) Word32 Source # 
Instance details

Defined in LndClient.Data.Newtype