btc-lsp-0.1.0.0: Lightning service provider
Safe HaskellSafe-Inferred
LanguageHaskell2010

BtcLsp.Data.Type

Documentation

data Nonce Source #

Instances

Instances details
Out Nonce Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

docPrec :: Int -> Nonce -> Doc #

doc :: Nonce -> Doc #

docList :: [Nonce] -> Doc #

Generic Nonce Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep Nonce :: Type -> Type #

Methods

from :: Nonce -> Rep Nonce x #

to :: Rep Nonce x -> Nonce #

Read Nonce Source # 
Instance details

Defined in BtcLsp.Data.Type

Show Nonce Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

showsPrec :: Int -> Nonce -> ShowS #

show :: Nonce -> String #

showList :: [Nonce] -> ShowS #

Eq Nonce Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

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

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

Ord Nonce Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

compare :: Nonce -> Nonce -> Ordering #

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

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

(>) :: Nonce -> Nonce -> Bool #

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

max :: Nonce -> Nonce -> Nonce #

min :: Nonce -> Nonce -> Nonce #

PersistField Nonce Source # 
Instance details

Defined in BtcLsp.Data.Type

PersistFieldSql Nonce Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

sqlType :: Proxy Nonce -> SqlType #

From Word64 Nonce Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Word64 -> Nonce

From Nonce Word64 Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Nonce -> Word64

From Nonce Nonce Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

Methods

from :: Nonce0 -> Nonce

From Nonce Nonce Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

Methods

from :: Nonce -> Nonce0

SymbolToField "latestNonce" User Nonce Source # 
Instance details

Defined in BtcLsp.Storage.Model

type Rep Nonce Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep Nonce = D1 ('MetaData "Nonce" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'True) (C1 ('MetaCons "Nonce" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))

newtype LnInvoice (mrel :: MoneyRelation) Source #

Constructors

LnInvoice PaymentRequest 

Instances

Instances details
From FundLnInvoice (LnInvoice 'Fund) Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

From LnInvoice (LnInvoice mrel) Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

Methods

from :: LnInvoice -> LnInvoice0 mrel

From PaymentRequest (LnInvoice mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: PaymentRequest -> LnInvoice mrel

From Text (LnInvoice mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Text -> LnInvoice mrel

Out (LnInvoice mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

docPrec :: Int -> LnInvoice mrel -> Doc #

doc :: LnInvoice mrel -> Doc #

docList :: [LnInvoice mrel] -> Doc #

Generic (LnInvoice mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep (LnInvoice mrel) :: Type -> Type #

Methods

from :: LnInvoice mrel -> Rep (LnInvoice mrel) x #

to :: Rep (LnInvoice mrel) x -> LnInvoice mrel #

Show (LnInvoice mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

showsPrec :: Int -> LnInvoice mrel -> ShowS #

show :: LnInvoice mrel -> String #

showList :: [LnInvoice mrel] -> ShowS #

Eq (LnInvoice mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

(==) :: LnInvoice mrel -> LnInvoice mrel -> Bool #

(/=) :: LnInvoice mrel -> LnInvoice mrel -> Bool #

PathPiece (LnInvoice mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

fromPathPiece :: Text -> Maybe (LnInvoice mrel) #

toPathPiece :: LnInvoice mrel -> Text #

PersistField (LnInvoice mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

PersistFieldSql (LnInvoice mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

sqlType :: Proxy (LnInvoice mrel) -> SqlType #

From (LnInvoice 'Fund) FundLnInvoice Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

From (LnInvoice mrel) LnInvoice Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

Methods

from :: LnInvoice0 mrel -> LnInvoice

From (LnInvoice mrel) PaymentRequest Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: LnInvoice mrel -> PaymentRequest

From (LnInvoice mrel) Text Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: LnInvoice mrel -> Text

type Rep (LnInvoice mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep (LnInvoice mrel) = D1 ('MetaData "LnInvoice" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'True) (C1 ('MetaCons "LnInvoice" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PaymentRequest)))

data LnInvoiceStatus Source #

Instances

Instances details
Out LnInvoiceStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

Generic LnInvoiceStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep LnInvoiceStatus :: Type -> Type #

Read LnInvoiceStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

Show LnInvoiceStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

Eq LnInvoiceStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

PersistField LnInvoiceStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

PersistFieldSql LnInvoiceStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep LnInvoiceStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep LnInvoiceStatus = D1 ('MetaData "LnInvoiceStatus" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'False) ((C1 ('MetaCons "LnInvoiceStatusNew" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LnInvoiceStatusLocked" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LnInvoiceStatusSettled" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LnInvoiceStatusCancelled" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LnInvoiceStatusExpired" 'PrefixI 'False) (U1 :: Type -> Type))))

data LnChanStatus Source #

Instances

Instances details
Out LnChanStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

Generic LnChanStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep LnChanStatus :: Type -> Type #

Read LnChanStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

Show LnChanStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

Eq LnChanStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

Ord LnChanStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

PersistField LnChanStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

PersistFieldSql LnChanStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

SymbolToField "status" LnChan LnChanStatus Source # 
Instance details

Defined in BtcLsp.Storage.Model

type Rep LnChanStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep LnChanStatus = D1 ('MetaData "LnChanStatus" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'False) ((C1 ('MetaCons "LnChanStatusPendingOpen" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LnChanStatusOpened" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LnChanStatusActive" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "LnChanStatusFullyResolved" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LnChanStatusInactive" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LnChanStatusPendingClose" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LnChanStatusClosed" 'PrefixI 'False) (U1 :: Type -> Type))))

newtype Liquidity (dir :: Direction) Source #

Constructors

Liquidity 

Fields

Instances

Instances details
Out (Liquidity dir) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

docPrec :: Int -> Liquidity dir -> Doc #

doc :: Liquidity dir -> Doc #

docList :: [Liquidity dir] -> Doc #

Generic (Liquidity dir) Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep (Liquidity dir) :: Type -> Type #

Methods

from :: Liquidity dir -> Rep (Liquidity dir) x #

to :: Rep (Liquidity dir) x -> Liquidity dir #

Num (Liquidity dir) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

(+) :: Liquidity dir -> Liquidity dir -> Liquidity dir #

(-) :: Liquidity dir -> Liquidity dir -> Liquidity dir #

(*) :: Liquidity dir -> Liquidity dir -> Liquidity dir #

negate :: Liquidity dir -> Liquidity dir #

abs :: Liquidity dir -> Liquidity dir #

signum :: Liquidity dir -> Liquidity dir #

fromInteger :: Integer -> Liquidity dir #

Read (Liquidity dir) Source # 
Instance details

Defined in BtcLsp.Data.Type

Show (Liquidity dir) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

showsPrec :: Int -> Liquidity dir -> ShowS #

show :: Liquidity dir -> String #

showList :: [Liquidity dir] -> ShowS #

Eq (Liquidity dir) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

(==) :: Liquidity dir -> Liquidity dir -> Bool #

(/=) :: Liquidity dir -> Liquidity dir -> Bool #

Ord (Liquidity dir) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

compare :: Liquidity dir -> Liquidity dir -> Ordering #

(<) :: Liquidity dir -> Liquidity dir -> Bool #

(<=) :: Liquidity dir -> Liquidity dir -> Bool #

(>) :: Liquidity dir -> Liquidity dir -> Bool #

(>=) :: Liquidity dir -> Liquidity dir -> Bool #

max :: Liquidity dir -> Liquidity dir -> Liquidity dir #

min :: Liquidity dir -> Liquidity dir -> Liquidity dir #

type Rep (Liquidity dir) Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep (Liquidity dir) = D1 ('MetaData "Liquidity" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'True) (C1 ('MetaCons "Liquidity" 'PrefixI 'True) (S1 ('MetaSel ('Just "unLiquidity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MSat)))

newtype Money (owner :: Owner) (btcl :: BitcoinLayer) (mrel :: MoneyRelation) Source #

Constructors

Money 

Fields

Instances

Instances details
SymbolToField "amount" SwapUtxo (Money 'Usr 'OnChain 'Fund) Source # 
Instance details

Defined in BtcLsp.Storage.Model

SymbolToField "chanCapLsp" SwapIntoLn (Money 'Lsp 'Ln 'Fund) Source # 
Instance details

Defined in BtcLsp.Storage.Model

SymbolToField "chanCapUser" SwapIntoLn (Money 'Usr 'Ln 'Fund) Source # 
Instance details

Defined in BtcLsp.Storage.Model

SymbolToField "feeLsp" SwapIntoLn (Money 'Lsp 'OnChain 'Gain) Source # 
Instance details

Defined in BtcLsp.Storage.Model

SymbolToField "feeMiner" SwapIntoLn (Money 'Lsp 'OnChain 'Loss) Source # 
Instance details

Defined in BtcLsp.Storage.Model

From Word64 (Money owner btcl mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Word64 -> Money owner btcl mrel

From MSat (Money owner btcl mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: MSat -> Money owner btcl mrel

TryFrom Rational (Money owner btcl mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

tryFrom :: Rational -> Either (TryFromException Rational (Money owner btcl mrel)) (Money owner btcl mrel)

TryFrom Natural (Money owner btcl mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

tryFrom :: Natural -> Either (TryFromException Natural (Money owner btcl mrel)) (Money owner btcl mrel)

TryFrom (Ratio Natural) (Money owner btcl mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

tryFrom :: Ratio Natural -> Either (TryFromException (Ratio Natural) (Money owner btcl mrel)) (Money owner btcl mrel)

Out (Money owner btcl mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

docPrec :: Int -> Money owner btcl mrel -> Doc #

doc :: Money owner btcl mrel -> Doc #

docList :: [Money owner btcl mrel] -> Doc #

Generic (Money owner btcl mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep (Money owner btcl mrel) :: Type -> Type #

Methods

from :: Money owner btcl mrel -> Rep (Money owner btcl mrel) x #

to :: Rep (Money owner btcl mrel) x -> Money owner btcl mrel #

Num (Money owner btcl mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

(+) :: Money owner btcl mrel -> Money owner btcl mrel -> Money owner btcl mrel #

(-) :: Money owner btcl mrel -> Money owner btcl mrel -> Money owner btcl mrel #

(*) :: Money owner btcl mrel -> Money owner btcl mrel -> Money owner btcl mrel #

negate :: Money owner btcl mrel -> Money owner btcl mrel #

abs :: Money owner btcl mrel -> Money owner btcl mrel #

signum :: Money owner btcl mrel -> Money owner btcl mrel #

fromInteger :: Integer -> Money owner btcl mrel #

Read (Money owner btcl mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

readsPrec :: Int -> ReadS (Money owner btcl mrel) #

readList :: ReadS [Money owner btcl mrel] #

readPrec :: ReadPrec (Money owner btcl mrel) #

readListPrec :: ReadPrec [Money owner btcl mrel] #

Show (Money owner btcl mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

showsPrec :: Int -> Money owner btcl mrel -> ShowS #

show :: Money owner btcl mrel -> String #

showList :: [Money owner btcl mrel] -> ShowS #

Eq (Money owner btcl mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

(==) :: Money owner btcl mrel -> Money owner btcl mrel -> Bool #

(/=) :: Money owner btcl mrel -> Money owner btcl mrel -> Bool #

Ord (Money owner btcl mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

compare :: Money owner btcl mrel -> Money owner btcl mrel -> Ordering #

(<) :: Money owner btcl mrel -> Money owner btcl mrel -> Bool #

(<=) :: Money owner btcl mrel -> Money owner btcl mrel -> Bool #

(>) :: Money owner btcl mrel -> Money owner btcl mrel -> Bool #

(>=) :: Money owner btcl mrel -> Money owner btcl mrel -> Bool #

max :: Money owner btcl mrel -> Money owner btcl mrel -> Money owner btcl mrel #

min :: Money owner btcl mrel -> Money owner btcl mrel -> Money owner btcl mrel #

PersistField (Money owner btcl mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

toPersistValue :: Money owner btcl mrel -> PersistValue #

fromPersistValue :: PersistValue -> Either Text (Money owner btcl mrel) #

PersistFieldSql (Money owner btcl mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

sqlType :: Proxy (Money owner btcl mrel) -> SqlType #

ToMessage (Money owner btcl mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

toMessage :: Money owner btcl mrel -> Text #

From (Money 'Lsp btcl 'Gain) FeeMoney Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

Methods

from :: Money 'Lsp btcl 'Gain -> FeeMoney

From (Money 'Usr btcl 'Fund) LocalBalance Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

Methods

from :: Money 'Usr btcl 'Fund -> LocalBalance

From (Money owner btcl mrel) Rational Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Money owner btcl mrel -> Rational

From (Money owner btcl mrel) Word64 Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Money owner btcl mrel -> Word64

From (Money owner btcl mrel) Msat Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

Methods

from :: Money owner btcl mrel -> Msat

From (Money owner btcl mrel) MSat Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Money owner btcl mrel -> MSat

From (Money owner btcl mrel) Natural Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Money owner btcl mrel -> Natural

From (Money owner btcl mrel) (Ratio Natural) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Money owner btcl mrel -> Ratio Natural

type Rep (Money owner btcl mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep (Money owner btcl mrel) = D1 ('MetaData "Money" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'True) (C1 ('MetaCons "Money" 'PrefixI 'True) (S1 ('MetaSel ('Just "unMoney") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MSat)))

newtype FeeRate Source #

Constructors

FeeRate (Ratio Word64) 

Instances

Instances details
Generic FeeRate Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep FeeRate :: Type -> Type #

Methods

from :: FeeRate -> Rep FeeRate x #

to :: Rep FeeRate x -> FeeRate #

Show FeeRate Source # 
Instance details

Defined in BtcLsp.Data.Type

Eq FeeRate Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

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

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

Ord FeeRate Source # 
Instance details

Defined in BtcLsp.Data.Type

ToMessage FeeRate Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

toMessage :: FeeRate -> Text #

From FeeRate Rational Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: FeeRate -> Rational

From FeeRate FeeRate Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

Methods

from :: FeeRate0 -> FeeRate

From FeeRate Urational Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

Methods

from :: FeeRate -> Urational

TryFrom Rational FeeRate Source # 
Instance details

Defined in BtcLsp.Data.Type

From FeeRate (Ratio Word64) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: FeeRate -> Ratio Word64

From FeeRate (Ratio Natural) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: FeeRate -> Ratio Natural

From (Ratio Word64) FeeRate Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Ratio Word64 -> FeeRate

type Rep FeeRate Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep FeeRate = D1 ('MetaData "FeeRate" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'True) (C1 ('MetaCons "FeeRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ratio Word64))))

newtype UnsafeOnChainAddress (mrel :: MoneyRelation) Source #

Instances

Instances details
From RefundOnChainAddress (UnsafeOnChainAddress 'Refund) Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

From OnChainAddress (UnsafeOnChainAddress 'Refund) Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

From Text (UnsafeOnChainAddress mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Text -> UnsafeOnChainAddress mrel

Out (UnsafeOnChainAddress mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Generic (UnsafeOnChainAddress mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep (UnsafeOnChainAddress mrel) :: Type -> Type #

Read (UnsafeOnChainAddress mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Show (UnsafeOnChainAddress mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Eq (UnsafeOnChainAddress mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Ord (UnsafeOnChainAddress mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

PathPiece (UnsafeOnChainAddress mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

PersistField (UnsafeOnChainAddress mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

PersistFieldSql (UnsafeOnChainAddress mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

From (UnsafeOnChainAddress mrel) Text Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: UnsafeOnChainAddress mrel -> Text

type Rep (UnsafeOnChainAddress mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep (UnsafeOnChainAddress mrel) = D1 ('MetaData "UnsafeOnChainAddress" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'True) (C1 ('MetaCons "UnsafeOnChainAddress" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype Seconds Source #

Constructors

Seconds Word64 

Instances

Instances details
Out Seconds Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

docPrec :: Int -> Seconds -> Doc #

doc :: Seconds -> Doc #

docList :: [Seconds] -> Doc #

Generic Seconds Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep Seconds :: Type -> Type #

Methods

from :: Seconds -> Rep Seconds x #

to :: Rep Seconds x -> Seconds #

Num Seconds Source # 
Instance details

Defined in BtcLsp.Data.Type

Show Seconds Source # 
Instance details

Defined in BtcLsp.Data.Type

Eq Seconds Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

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

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

Ord Seconds Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep Seconds Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep Seconds = D1 ('MetaData "Seconds" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'True) (C1 ('MetaCons "Seconds" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))

data LogFormat Source #

Constructors

Bracket 
JSON 

Instances

Instances details
Read LogFormat Source # 
Instance details

Defined in BtcLsp.Data.Type

data YesodLog Source #

Instances

Instances details
FromJSON YesodLog Source # 
Instance details

Defined in BtcLsp.Data.Type

Generic YesodLog Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep YesodLog :: Type -> Type #

Methods

from :: YesodLog -> Rep YesodLog x #

to :: Rep YesodLog x -> YesodLog #

Read YesodLog Source # 
Instance details

Defined in BtcLsp.Data.Type

Show YesodLog Source # 
Instance details

Defined in BtcLsp.Data.Type

Eq YesodLog Source # 
Instance details

Defined in BtcLsp.Data.Type

Ord YesodLog Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep YesodLog Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep YesodLog = D1 ('MetaData "YesodLog" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'False) (C1 ('MetaCons "YesodLogAll" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "YesodLogNoMain" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "YesodLogNothing" 'PrefixI 'False) (U1 :: Type -> Type)))

newtype MicroSeconds Source #

Constructors

MicroSeconds Integer 

Instances

Instances details
Out MicroSeconds Source # 
Instance details

Defined in BtcLsp.Data.Type

Generic MicroSeconds Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep MicroSeconds :: Type -> Type #

Num MicroSeconds Source # 
Instance details

Defined in BtcLsp.Data.Type

Show MicroSeconds Source # 
Instance details

Defined in BtcLsp.Data.Type

Eq MicroSeconds Source # 
Instance details

Defined in BtcLsp.Data.Type

Ord MicroSeconds Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep MicroSeconds Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep MicroSeconds = D1 ('MetaData "MicroSeconds" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'True) (C1 ('MetaCons "MicroSeconds" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))

data SwapStatus Source #

Constructors

SwapWaitingFundChain

Waiting on-chain funding trx with given amt from user with some confirmations.

SwapWaitingPeer

Swap has been funded on-chain, need to open LN channel now.

SwapWaitingChan

Waiting channel opening trx to be mined with some confirmations.

SwapSucceeded

Final statuses

SwapExpired 

Instances

Instances details
Out SwapStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

Bounded SwapStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

Enum SwapStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

Generic SwapStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep SwapStatus :: Type -> Type #

Read SwapStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

Show SwapStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

Eq SwapStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

Ord SwapStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

PathPiece SwapStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

PersistField SwapStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

PersistFieldSql SwapStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

SymbolToField "status" SwapIntoLn SwapStatus Source # 
Instance details

Defined in BtcLsp.Storage.Model

type Rep SwapStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep SwapStatus = D1 ('MetaData "SwapStatus" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'False) ((C1 ('MetaCons "SwapWaitingFundChain" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SwapWaitingPeer" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SwapWaitingChan" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SwapSucceeded" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SwapExpired" 'PrefixI 'False) (U1 :: Type -> Type))))

data Failure Source #

Instances

Instances details
Out Failure Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

docPrec :: Int -> Failure -> Doc #

doc :: Failure -> Doc #

docList :: [Failure] -> Doc #

Generic Failure Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep Failure :: Type -> Type #

Methods

from :: Failure -> Rep Failure x #

to :: Rep Failure x -> Failure #

Show Failure Source # 
Instance details

Defined in BtcLsp.Data.Type

Eq Failure Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

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

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

type Rep Failure Source # 
Instance details

Defined in BtcLsp.Data.Type

data FailureInternal Source #

Instances

Instances details
Out FailureInternal Source # 
Instance details

Defined in BtcLsp.Data.Type

Generic FailureInternal Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep FailureInternal :: Type -> Type #

Show FailureInternal Source # 
Instance details

Defined in BtcLsp.Data.Type

Eq FailureInternal Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep FailureInternal Source # 
Instance details

Defined in BtcLsp.Data.Type

data FailureInput Source #

Instances

Instances details
Out FailureInput Source # 
Instance details

Defined in BtcLsp.Data.Type

Generic FailureInput Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep FailureInput :: Type -> Type #

Show FailureInput Source # 
Instance details

Defined in BtcLsp.Data.Type

Eq FailureInput Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep FailureInput Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep FailureInput = D1 ('MetaData "FailureInput" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'False) (C1 ('MetaCons "FailureNonce" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FailureNonSegwitAddr" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FailureNonValidAddr" 'PrefixI 'False) (U1 :: Type -> Type)))

tryFailureE :: forall source target. (Show source, Typeable source, Typeable target) => Text -> Either (TryFromException source target) target -> Either Failure target Source #

tryFailureT :: forall source target m. (Show source, Typeable source, Typeable target, Monad m) => Text -> Either (TryFromException source target) target -> ExceptT Failure m target Source #

tryFromE :: forall source target. (Show source, Typeable source, Typeable target, TryFrom source target, 'False ~ (source == target)) => Text -> source -> Either Failure target Source #

tryFromT :: forall source target m. (Show source, Typeable source, Typeable target, TryFrom source target, Monad m, 'False ~ (source == target)) => Text -> source -> ExceptT Failure m target Source #

data SocketAddress Source #

Instances

Instances details
Out SocketAddress Source # 
Instance details

Defined in BtcLsp.Data.Type

Generic SocketAddress Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep SocketAddress :: Type -> Type #

Show SocketAddress Source # 
Instance details

Defined in BtcLsp.Data.Type

Eq SocketAddress Source # 
Instance details

Defined in BtcLsp.Data.Type

Ord SocketAddress Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep SocketAddress Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep SocketAddress = D1 ('MetaData "SocketAddress" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'False) (C1 ('MetaCons "SocketAddress" 'PrefixI 'True) (S1 ('MetaSel ('Just "socketAddressHost") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 HostName) :*: S1 ('MetaSel ('Just "socketAddressPort") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PortNumber)))

newtype BlkHash Source #

Constructors

BlkHash BlockHash 

Instances

Instances details
Out BlkHash Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

docPrec :: Int -> BlkHash -> Doc #

doc :: BlkHash -> Doc #

docList :: [BlkHash] -> Doc #

Generic BlkHash Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep BlkHash :: Type -> Type #

Methods

from :: BlkHash -> Rep BlkHash x #

to :: Rep BlkHash x -> BlkHash #

Show BlkHash Source # 
Instance details

Defined in BtcLsp.Data.Type

Eq BlkHash Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

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

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

Ord BlkHash Source # 
Instance details

Defined in BtcLsp.Data.Type

PersistField BlkHash Source # 
Instance details

Defined in BtcLsp.Data.Type

PersistFieldSql BlkHash Source # 
Instance details

Defined in BtcLsp.Data.Type

From BlkHash BlockHash Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: BlkHash -> BlockHash

From BlockHash BlkHash Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: BlockHash -> BlkHash

SymbolToField "hash" Block BlkHash Source # 
Instance details

Defined in BtcLsp.Storage.Model

type Rep BlkHash Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep BlkHash = D1 ('MetaData "BlkHash" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'True) (C1 ('MetaCons "BlkHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockHash)))

newtype BlkHeight Source #

Constructors

BlkHeight Word64 

Instances

Instances details
Out BlkHeight Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

docPrec :: Int -> BlkHeight -> Doc #

doc :: BlkHeight -> Doc #

docList :: [BlkHeight] -> Doc #

ToJSON BlkHeight Source # 
Instance details

Defined in BtcLsp.Data.Type

Generic BlkHeight Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep BlkHeight :: Type -> Type #

Num BlkHeight Source # 
Instance details

Defined in BtcLsp.Data.Type

Show BlkHeight Source # 
Instance details

Defined in BtcLsp.Data.Type

Eq BlkHeight Source # 
Instance details

Defined in BtcLsp.Data.Type

Ord BlkHeight Source # 
Instance details

Defined in BtcLsp.Data.Type

PersistField BlkHeight Source # 
Instance details

Defined in BtcLsp.Data.Type

PersistFieldSql BlkHeight Source # 
Instance details

Defined in BtcLsp.Data.Type

From Word64 BlkHeight Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Word64 -> BlkHeight

From BlkHeight Word64 Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: BlkHeight -> Word64

From BlkHeight BlockHeight Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: BlkHeight -> BlockHeight

From BlkHeight Natural Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: BlkHeight -> Natural

TryFrom BlockHeight BlkHeight Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

tryFrom :: BlockHeight -> Either (TryFromException BlockHeight BlkHeight) BlkHeight

SymbolToField "height" Block BlkHeight Source # 
Instance details

Defined in BtcLsp.Storage.Model

type Rep BlkHeight Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep BlkHeight = D1 ('MetaData "BlkHeight" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'True) (C1 ('MetaCons "BlkHeight" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))

data BlkStatus Source #

Constructors

BlkConfirmed 
BlkOrphan 

Instances

Instances details
Out BlkStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

docPrec :: Int -> BlkStatus -> Doc #

doc :: BlkStatus -> Doc #

docList :: [BlkStatus] -> Doc #

Generic BlkStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep BlkStatus :: Type -> Type #

Read BlkStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

Show BlkStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

Eq BlkStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

Ord BlkStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

PersistField BlkStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

PersistFieldSql BlkStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

SymbolToField "status" Block BlkStatus Source # 
Instance details

Defined in BtcLsp.Storage.Model

type Rep BlkStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep BlkStatus = D1 ('MetaData "BlkStatus" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'False) (C1 ('MetaCons "BlkConfirmed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlkOrphan" 'PrefixI 'False) (U1 :: Type -> Type))

data SwapUtxoStatus Source #

Instances

Instances details
Out SwapUtxoStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

Generic SwapUtxoStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep SwapUtxoStatus :: Type -> Type #

Read SwapUtxoStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

Show SwapUtxoStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

Eq SwapUtxoStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

Ord SwapUtxoStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

PersistField SwapUtxoStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

PersistFieldSql SwapUtxoStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

SymbolToField "status" SwapUtxo SwapUtxoStatus Source # 
Instance details

Defined in BtcLsp.Storage.Model

type Rep SwapUtxoStatus Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep SwapUtxoStatus = D1 ('MetaData "SwapUtxoStatus" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'False) ((C1 ('MetaCons "SwapUtxoUnspent" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SwapUtxoUnspentDust" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SwapUtxoUnspentChanReserve" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "SwapUtxoSpentChanSwapped" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SwapUtxoSpentRefund" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SwapUtxoOrphan" 'PrefixI 'False) (U1 :: Type -> Type))))

data Privacy Source #

Constructors

Public 
Private 

Instances

Instances details
Out Privacy Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

docPrec :: Int -> Privacy -> Doc #

doc :: Privacy -> Doc #

docList :: [Privacy] -> Doc #

Bounded Privacy Source # 
Instance details

Defined in BtcLsp.Data.Type

Enum Privacy Source # 
Instance details

Defined in BtcLsp.Data.Type

Generic Privacy Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep Privacy :: Type -> Type #

Methods

from :: Privacy -> Rep Privacy x #

to :: Rep Privacy x -> Privacy #

Read Privacy Source # 
Instance details

Defined in BtcLsp.Data.Type

Show Privacy Source # 
Instance details

Defined in BtcLsp.Data.Type

Eq Privacy Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

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

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

Ord Privacy Source # 
Instance details

Defined in BtcLsp.Data.Type

PersistField Privacy Source # 
Instance details

Defined in BtcLsp.Data.Type

PersistFieldSql Privacy Source # 
Instance details

Defined in BtcLsp.Data.Type

From Privacy Privacy Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

Methods

from :: Privacy0 -> Privacy

From Privacy Privacy Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

Methods

from :: Privacy -> Privacy0

SymbolToField "privacy" SwapIntoLn Privacy Source # 
Instance details

Defined in BtcLsp.Storage.Model

type Rep Privacy Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep Privacy = D1 ('MetaData "Privacy" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'False) (C1 ('MetaCons "Public" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Private" 'PrefixI 'False) (U1 :: Type -> Type))

newtype NodePubKeyHex Source #

Constructors

NodePubKeyHex Text 

Instances

Instances details
Out NodePubKeyHex Source # 
Instance details

Defined in BtcLsp.Data.Type

IsString NodePubKeyHex Source # 
Instance details

Defined in BtcLsp.Data.Type

Generic NodePubKeyHex Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep NodePubKeyHex :: Type -> Type #

Read NodePubKeyHex Source # 
Instance details

Defined in BtcLsp.Data.Type

Show NodePubKeyHex Source # 
Instance details

Defined in BtcLsp.Data.Type

Eq NodePubKeyHex Source # 
Instance details

Defined in BtcLsp.Data.Type

Ord NodePubKeyHex Source # 
Instance details

Defined in BtcLsp.Data.Type

From NodePubKeyHex Text Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: NodePubKeyHex -> Text

From Text NodePubKeyHex Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Text -> NodePubKeyHex

TryFrom NodePubKey NodePubKeyHex Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep NodePubKeyHex Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep NodePubKeyHex = D1 ('MetaData "NodePubKeyHex" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'True) (C1 ('MetaCons "NodePubKeyHex" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data NodeUri Source #

Instances

Instances details
Out NodeUri Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

docPrec :: Int -> NodeUri -> Doc #

doc :: NodeUri -> Doc #

docList :: [NodeUri] -> Doc #

Generic NodeUri Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep NodeUri :: Type -> Type #

Methods

from :: NodeUri -> Rep NodeUri x #

to :: Rep NodeUri x -> NodeUri #

Show NodeUri Source # 
Instance details

Defined in BtcLsp.Data.Type

Eq NodeUri Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

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

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

Ord NodeUri Source # 
Instance details

Defined in BtcLsp.Data.Type

TryFrom NodeUri NodeUriHex Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep NodeUri Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep NodeUri = D1 ('MetaData "NodeUri" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'False) (C1 ('MetaCons "NodeUri" 'PrefixI 'True) (S1 ('MetaSel ('Just "nodeUriPubKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 NodePubKey) :*: S1 ('MetaSel ('Just "nodeUriSocketAddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SocketAddress)))

newtype NodeUriHex Source #

Constructors

NodeUriHex Text 

Instances

Instances details
Out NodeUriHex Source # 
Instance details

Defined in BtcLsp.Data.Type

IsString NodeUriHex Source # 
Instance details

Defined in BtcLsp.Data.Type

Generic NodeUriHex Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep NodeUriHex :: Type -> Type #

Read NodeUriHex Source # 
Instance details

Defined in BtcLsp.Data.Type

Show NodeUriHex Source # 
Instance details

Defined in BtcLsp.Data.Type

Eq NodeUriHex Source # 
Instance details

Defined in BtcLsp.Data.Type

Ord NodeUriHex Source # 
Instance details

Defined in BtcLsp.Data.Type

From NodeUriHex Text Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: NodeUriHex -> Text

From Text NodeUriHex Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Text -> NodeUriHex

TryFrom NodeUri NodeUriHex Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep NodeUriHex Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep NodeUriHex = D1 ('MetaData "NodeUriHex" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'True) (C1 ('MetaCons "NodeUriHex" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype UtxoLockId Source #

Constructors

UtxoLockId ByteString 

Instances

Instances details
Out UtxoLockId Source # 
Instance details

Defined in BtcLsp.Data.Type

Generic UtxoLockId Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep UtxoLockId :: Type -> Type #

Read UtxoLockId Source # 
Instance details

Defined in BtcLsp.Data.Type

Show UtxoLockId Source # 
Instance details

Defined in BtcLsp.Data.Type

Eq UtxoLockId Source # 
Instance details

Defined in BtcLsp.Data.Type

Ord UtxoLockId Source # 
Instance details

Defined in BtcLsp.Data.Type

PersistField UtxoLockId Source # 
Instance details

Defined in BtcLsp.Data.Type

PersistFieldSql UtxoLockId Source # 
Instance details

Defined in BtcLsp.Data.Type

SymbolToField "lockId" SwapUtxo (Maybe UtxoLockId) Source # 
Instance details

Defined in BtcLsp.Storage.Model

type Rep UtxoLockId Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep UtxoLockId = D1 ('MetaData "UtxoLockId" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'True) (C1 ('MetaCons "UtxoLockId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

newtype RHashHex Source #

Constructors

RHashHex 

Fields

Instances

Instances details
Out RHashHex Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

docPrec :: Int -> RHashHex -> Doc #

doc :: RHashHex -> Doc #

docList :: [RHashHex] -> Doc #

Generic RHashHex Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep RHashHex :: Type -> Type #

Methods

from :: RHashHex -> Rep RHashHex x #

to :: Rep RHashHex x -> RHashHex #

Read RHashHex Source # 
Instance details

Defined in BtcLsp.Data.Type

Show RHashHex Source # 
Instance details

Defined in BtcLsp.Data.Type

Eq RHashHex Source # 
Instance details

Defined in BtcLsp.Data.Type

Ord RHashHex Source # 
Instance details

Defined in BtcLsp.Data.Type

PathPiece RHashHex Source # 
Instance details

Defined in BtcLsp.Data.Type

From RHashHex RHash Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: RHashHex -> RHash

From RHashHex Text Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: RHashHex -> Text

From RHash RHashHex Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: RHash -> RHashHex

From Text RHashHex Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Text -> RHashHex

type Rep RHashHex Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep RHashHex = D1 ('MetaData "RHashHex" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'True) (C1 ('MetaCons "RHashHex" 'PrefixI 'True) (S1 ('MetaSel ('Just "unRHashHex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data Uuid (tab :: Table) Source #

Instances

Instances details
SymbolToField "uuid" SwapIntoLn (Uuid 'SwapIntoLnTable) Source # 
Instance details

Defined in BtcLsp.Storage.Model

Out (Uuid tab) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

docPrec :: Int -> Uuid tab -> Doc #

doc :: Uuid tab -> Doc #

docList :: [Uuid tab] -> Doc #

Generic (Uuid tab) Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep (Uuid tab) :: Type -> Type #

Methods

from :: Uuid tab -> Rep (Uuid tab) x #

to :: Rep (Uuid tab) x -> Uuid tab #

Read (Uuid tab) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

readsPrec :: Int -> ReadS (Uuid tab) #

readList :: ReadS [Uuid tab] #

readPrec :: ReadPrec (Uuid tab) #

readListPrec :: ReadPrec [Uuid tab] #

Show (Uuid tab) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

showsPrec :: Int -> Uuid tab -> ShowS #

show :: Uuid tab -> String #

showList :: [Uuid tab] -> ShowS #

Eq (Uuid tab) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

(==) :: Uuid tab -> Uuid tab -> Bool #

(/=) :: Uuid tab -> Uuid tab -> Bool #

Ord (Uuid tab) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

compare :: Uuid tab -> Uuid tab -> Ordering #

(<) :: Uuid tab -> Uuid tab -> Bool #

(<=) :: Uuid tab -> Uuid tab -> Bool #

(>) :: Uuid tab -> Uuid tab -> Bool #

(>=) :: Uuid tab -> Uuid tab -> Bool #

max :: Uuid tab -> Uuid tab -> Uuid tab #

min :: Uuid tab -> Uuid tab -> Uuid tab #

PathPiece (Uuid tab) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

fromPathPiece :: Text -> Maybe (Uuid tab) #

toPathPiece :: Uuid tab -> Text #

PersistField (Uuid tab) Source # 
Instance details

Defined in BtcLsp.Data.Type

PersistFieldSql (Uuid tab) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

sqlType :: Proxy (Uuid tab) -> SqlType #

ToMessage (Uuid tab) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

toMessage :: Uuid tab -> Text #

type Rep (Uuid tab) Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep (Uuid tab) = D1 ('MetaData "Uuid" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'True) (C1 ('MetaCons "Uuid" 'PrefixI 'True) (S1 ('MetaSel ('Just "unUuid'") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UUID)))

unUuid :: Uuid tab -> UUID Source #

newUuid :: MonadIO m => m (Uuid tab) Source #

newtype Vbyte Source #

Constructors

Vbyte 

Fields

Instances

Instances details
Out Vbyte Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

docPrec :: Int -> Vbyte -> Doc #

doc :: Vbyte -> Doc #

docList :: [Vbyte] -> Doc #

Generic Vbyte Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep Vbyte :: Type -> Type #

Methods

from :: Vbyte -> Rep Vbyte x #

to :: Rep Vbyte x -> Vbyte #

Num Vbyte Source # 
Instance details

Defined in BtcLsp.Data.Type

Show Vbyte Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

showsPrec :: Int -> Vbyte -> ShowS #

show :: Vbyte -> String #

showList :: [Vbyte] -> ShowS #

Eq Vbyte Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

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

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

Ord Vbyte Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

compare :: Vbyte -> Vbyte -> Ordering #

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

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

(>) :: Vbyte -> Vbyte -> Bool #

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

max :: Vbyte -> Vbyte -> Vbyte #

min :: Vbyte -> Vbyte -> Vbyte #

From Vbyte (Ratio Natural) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Vbyte -> Ratio Natural

From (Ratio Natural) Vbyte Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Ratio Natural -> Vbyte

type Rep Vbyte Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep Vbyte = D1 ('MetaData "Vbyte" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'True) (C1 ('MetaCons "Vbyte" 'PrefixI 'True) (S1 ('MetaSel ('Just "unVbyte") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ratio Natural))))

newtype RowQty Source #

Constructors

RowQty 

Fields

Instances

Instances details
Out RowQty Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

docPrec :: Int -> RowQty -> Doc #

doc :: RowQty -> Doc #

docList :: [RowQty] -> Doc #

Generic RowQty Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep RowQty :: Type -> Type #

Methods

from :: RowQty -> Rep RowQty x #

to :: Rep RowQty x -> RowQty #

Show RowQty Source # 
Instance details

Defined in BtcLsp.Data.Type

Eq RowQty Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

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

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

Ord RowQty Source # 
Instance details

Defined in BtcLsp.Data.Type

From Int64 RowQty Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Int64 -> RowQty

From RowQty Int64 Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: RowQty -> Int64

From Int RowQty Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Int -> RowQty

type Rep RowQty Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep RowQty = D1 ('MetaData "RowQty" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'True) (C1 ('MetaCons "RowQty" 'PrefixI 'True) (S1 ('MetaSel ('Just "unRowQty") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64)))

data PsbtUtxo Source #

Constructors

PsbtUtxo 

Fields

Instances

Instances details
Out PsbtUtxo Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

docPrec :: Int -> PsbtUtxo -> Doc #

doc :: PsbtUtxo -> Doc #

docList :: [PsbtUtxo] -> Doc #

Generic PsbtUtxo Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep PsbtUtxo :: Type -> Type #

Methods

from :: PsbtUtxo -> Rep PsbtUtxo x #

to :: Rep PsbtUtxo x -> PsbtUtxo #

Show PsbtUtxo Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep PsbtUtxo Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep PsbtUtxo = D1 ('MetaData "PsbtUtxo" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'False) (C1 ('MetaCons "PsbtUtxo" 'PrefixI 'True) (S1 ('MetaSel ('Just "getOutPoint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 OutPoint) :*: (S1 ('MetaSel ('Just "getAmt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 MSat) :*: S1 ('MetaSel ('Just "getLockId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe UtxoLockId)))))

newtype SwapHash Source #

Constructors

SwapHash Text 

Instances

Instances details
Out SwapHash Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

docPrec :: Int -> SwapHash -> Doc #

doc :: SwapHash -> Doc #

docList :: [SwapHash] -> Doc #

ToJSON SwapHash Source # 
Instance details

Defined in BtcLsp.Data.Type

Generic SwapHash Source # 
Instance details

Defined in BtcLsp.Data.Type

Associated Types

type Rep SwapHash :: Type -> Type #

Methods

from :: SwapHash -> Rep SwapHash x #

to :: Rep SwapHash x -> SwapHash #

Read SwapHash Source # 
Instance details

Defined in BtcLsp.Data.Type

Show SwapHash Source # 
Instance details

Defined in BtcLsp.Data.Type

Eq SwapHash Source # 
Instance details

Defined in BtcLsp.Data.Type

PathPiece SwapHash Source # 
Instance details

Defined in BtcLsp.Data.Type

ToJavascript SwapHash Source # 
Instance details

Defined in BtcLsp.Data.Type

ToContent (Maybe SwapHash) Source # 
Instance details

Defined in BtcLsp.Data.Type

ToTypedContent (Maybe SwapHash) Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep SwapHash Source # 
Instance details

Defined in BtcLsp.Data.Type

type Rep SwapHash = D1 ('MetaData "SwapHash" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'True) (C1 ('MetaCons "SwapHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))