Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Documentation
Instances
Out Nonce Source # | |
Generic Nonce Source # | |
Read Nonce Source # | |
Show Nonce Source # | |
Eq Nonce Source # | |
Ord Nonce Source # | |
PersistField Nonce Source # | |
Defined in BtcLsp.Data.Type toPersistValue :: Nonce -> PersistValue # fromPersistValue :: PersistValue -> Either Text Nonce # | |
PersistFieldSql Nonce Source # | |
From Word64 Nonce Source # | |
Defined in BtcLsp.Data.Type | |
From Nonce Word64 Source # | |
Defined in BtcLsp.Data.Type | |
From Nonce Nonce Source # | |
Defined in BtcLsp.Grpc.Orphan | |
From Nonce Nonce Source # | |
Defined in BtcLsp.Grpc.Orphan | |
SymbolToField "latestNonce" User Nonce Source # | |
Defined in BtcLsp.Storage.Model | |
type Rep Nonce Source # | |
Defined in BtcLsp.Data.Type |
newtype LnInvoice (mrel :: MoneyRelation) Source #
LnInvoice PaymentRequest |
Instances
data LnInvoiceStatus Source #
LnInvoiceStatusNew | |
LnInvoiceStatusLocked | |
LnInvoiceStatusSettled | |
LnInvoiceStatusCancelled | |
LnInvoiceStatusExpired |
Instances
data LnChanStatus Source #
LnChanStatusPendingOpen | |
LnChanStatusOpened | |
LnChanStatusActive | |
LnChanStatusFullyResolved | |
LnChanStatusInactive | |
LnChanStatusPendingClose | |
LnChanStatusClosed |
Instances
newtype Liquidity (dir :: Direction) Source #
Instances
Out (Liquidity dir) Source # | |
Generic (Liquidity dir) Source # | |
Num (Liquidity dir) Source # | |
Defined in BtcLsp.Data.Type (+) :: 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 # | |
Show (Liquidity dir) Source # | |
Eq (Liquidity dir) Source # | |
Ord (Liquidity dir) Source # | |
Defined in BtcLsp.Data.Type 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 # | |
type Rep (Liquidity dir) Source # | |
Defined in BtcLsp.Data.Type |
newtype Money (owner :: Owner) (btcl :: BitcoinLayer) (mrel :: MoneyRelation) Source #
Instances
Instances
Generic FeeRate Source # | |
Show FeeRate Source # | |
Eq FeeRate Source # | |
Ord FeeRate Source # | |
ToMessage FeeRate Source # | |
Defined in BtcLsp.Data.Type | |
From FeeRate Rational Source # | |
Defined in BtcLsp.Data.Type | |
From FeeRate FeeRate Source # | |
Defined in BtcLsp.Grpc.Orphan | |
From FeeRate Urational Source # | |
Defined in BtcLsp.Grpc.Orphan | |
TryFrom Rational FeeRate Source # | |
Defined in BtcLsp.Data.Type | |
From FeeRate (Ratio Word64) Source # | |
Defined in BtcLsp.Data.Type | |
From FeeRate (Ratio Natural) Source # | |
Defined in BtcLsp.Data.Type | |
From (Ratio Word64) FeeRate Source # | |
Defined in BtcLsp.Data.Type | |
type Rep FeeRate Source # | |
newtype UnsafeOnChainAddress (mrel :: MoneyRelation) Source #
Instances
Instances
FromJSON YesodLog Source # | |
Generic YesodLog Source # | |
Read YesodLog Source # | |
Show YesodLog Source # | |
Eq YesodLog Source # | |
Ord YesodLog Source # | |
Defined in BtcLsp.Data.Type | |
type Rep YesodLog Source # | |
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 #
Instances
data SwapStatus Source #
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
swapStatusChain :: [SwapStatus] Source #
swapStatusLn :: [SwapStatus] Source #
swapStatusFinal :: [SwapStatus] Source #
Instances
Out Failure Source # | |
Generic Failure Source # | |
Show Failure Source # | |
Eq Failure Source # | |
type Rep Failure Source # | |
Defined in BtcLsp.Data.Type type Rep Failure = D1 ('MetaData "Failure" "BtcLsp.Data.Type" "btc-lsp-0.1.0.0-inplace" 'False) (C1 ('MetaCons "FailureInp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 FailureInput)) :+: C1 ('MetaCons "FailureInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 FailureInternal))) |
data FailureInternal Source #
Instances
data FailureInput Source #
Instances
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
BlkHash BlockHash |
Instances
Out BlkHash Source # | |
Generic BlkHash Source # | |
Show BlkHash Source # | |
Eq BlkHash Source # | |
Ord BlkHash Source # | |
PersistField BlkHash Source # | |
Defined in BtcLsp.Data.Type toPersistValue :: BlkHash -> PersistValue # | |
PersistFieldSql BlkHash Source # | |
From BlkHash BlockHash Source # | |
Defined in BtcLsp.Data.Type | |
From BlockHash BlkHash Source # | |
Defined in BtcLsp.Data.Type | |
SymbolToField "hash" Block BlkHash Source # | |
Defined in BtcLsp.Storage.Model | |
type Rep BlkHash Source # | |
Defined in BtcLsp.Data.Type |
Instances
Out BlkHeight Source # | |
ToJSON BlkHeight Source # | |
Defined in BtcLsp.Data.Type | |
Generic BlkHeight Source # | |
Num BlkHeight Source # | |
Show BlkHeight Source # | |
Eq BlkHeight Source # | |
Ord BlkHeight Source # | |
Defined in BtcLsp.Data.Type | |
PersistField BlkHeight Source # | |
Defined in BtcLsp.Data.Type | |
PersistFieldSql BlkHeight Source # | |
From Word64 BlkHeight Source # | |
Defined in BtcLsp.Data.Type | |
From BlkHeight Word64 Source # | |
Defined in BtcLsp.Data.Type | |
From BlkHeight BlockHeight Source # | |
Defined in BtcLsp.Data.Type | |
From BlkHeight Natural Source # | |
Defined in BtcLsp.Data.Type | |
TryFrom BlockHeight BlkHeight Source # | |
Defined in BtcLsp.Data.Type tryFrom :: BlockHeight -> Either (TryFromException BlockHeight BlkHeight) BlkHeight | |
SymbolToField "height" Block BlkHeight Source # | |
Defined in BtcLsp.Storage.Model | |
type Rep BlkHeight Source # | |
Defined in BtcLsp.Data.Type |
Instances
Out BlkStatus Source # | |
Generic BlkStatus Source # | |
Read BlkStatus Source # | |
Show BlkStatus Source # | |
Eq BlkStatus Source # | |
Ord BlkStatus Source # | |
Defined in BtcLsp.Data.Type | |
PersistField BlkStatus Source # | |
Defined in BtcLsp.Data.Type | |
PersistFieldSql BlkStatus Source # | |
SymbolToField "status" Block BlkStatus Source # | |
Defined in BtcLsp.Storage.Model | |
type Rep BlkStatus Source # | |
data SwapUtxoStatus Source #
SwapUtxoUnspent | |
SwapUtxoUnspentDust | |
SwapUtxoUnspentChanReserve | |
SwapUtxoSpentChanSwapped | |
SwapUtxoSpentRefund | |
SwapUtxoOrphan |
Instances
Instances
Out Privacy Source # | |
Bounded Privacy Source # | |
Enum Privacy Source # | |
Generic Privacy Source # | |
Read Privacy Source # | |
Show Privacy Source # | |
Eq Privacy Source # | |
Ord Privacy Source # | |
PersistField Privacy Source # | |
Defined in BtcLsp.Data.Type toPersistValue :: Privacy -> PersistValue # | |
PersistFieldSql Privacy Source # | |
From Privacy Privacy Source # | |
Defined in BtcLsp.Grpc.Orphan | |
From Privacy Privacy Source # | |
Defined in BtcLsp.Grpc.Orphan | |
SymbolToField "privacy" SwapIntoLn Privacy Source # | |
Defined in BtcLsp.Storage.Model | |
type Rep Privacy Source # | |
newtype NodePubKeyHex Source #
Instances
Instances
Out NodeUri Source # | |
Generic NodeUri Source # | |
Show NodeUri Source # | |
Eq NodeUri Source # | |
Ord NodeUri Source # | |
TryFrom NodeUri NodeUriHex Source # | |
Defined in BtcLsp.Data.Type | |
type Rep NodeUri Source # | |
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 #
Instances
newtype UtxoLockId Source #
Instances
Instances
Out RHashHex Source # | |
Generic RHashHex Source # | |
Read RHashHex Source # | |
Show RHashHex Source # | |
Eq RHashHex Source # | |
Ord RHashHex Source # | |
Defined in BtcLsp.Data.Type | |
PathPiece RHashHex Source # | |
Defined in BtcLsp.Data.Type fromPathPiece :: Text -> Maybe RHashHex # toPathPiece :: RHashHex -> Text # | |
From RHashHex RHash Source # | |
Defined in BtcLsp.Data.Type | |
From RHashHex Text Source # | |
Defined in BtcLsp.Data.Type | |
From RHash RHashHex Source # | |
Defined in BtcLsp.Data.Type | |
From Text RHashHex Source # | |
Defined in BtcLsp.Data.Type | |
type Rep RHashHex Source # | |
Defined in BtcLsp.Data.Type |
data Uuid (tab :: Table) Source #
Instances
SymbolToField "uuid" SwapIntoLn (Uuid 'SwapIntoLnTable) Source # | |
Defined in BtcLsp.Storage.Model | |
Out (Uuid tab) Source # | |
Generic (Uuid tab) Source # | |
Read (Uuid tab) Source # | |
Show (Uuid tab) Source # | |
Eq (Uuid tab) Source # | |
Ord (Uuid tab) Source # | |
Defined in BtcLsp.Data.Type | |
PathPiece (Uuid tab) Source # | |
Defined in BtcLsp.Data.Type fromPathPiece :: Text -> Maybe (Uuid tab) # toPathPiece :: Uuid tab -> Text # | |
PersistField (Uuid tab) Source # | |
Defined in BtcLsp.Data.Type toPersistValue :: Uuid tab -> PersistValue # fromPersistValue :: PersistValue -> Either Text (Uuid tab) # | |
PersistFieldSql (Uuid tab) Source # | |
ToMessage (Uuid tab) Source # | |
Defined in BtcLsp.Data.Type | |
type Rep (Uuid tab) Source # | |
Defined in BtcLsp.Data.Type |
Instances
Instances
Out RowQty Source # | |
Generic RowQty Source # | |
Show RowQty Source # | |
Eq RowQty Source # | |
Ord RowQty Source # | |
From Int64 RowQty Source # | |
Defined in BtcLsp.Data.Type | |
From RowQty Int64 Source # | |
Defined in BtcLsp.Data.Type | |
From Int RowQty Source # | |
Defined in BtcLsp.Data.Type | |
type Rep RowQty Source # | |
Defined in BtcLsp.Data.Type |
PsbtUtxo | |
|
Instances
Out PsbtUtxo Source # | |
Generic PsbtUtxo Source # | |
Show PsbtUtxo Source # | |
type Rep PsbtUtxo Source # | |
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))))) |
Instances
Out SwapHash Source # | |
ToJSON SwapHash Source # | |
Defined in BtcLsp.Data.Type | |
Generic SwapHash Source # | |
Read SwapHash Source # | |
Show SwapHash Source # | |
Eq SwapHash Source # | |
PathPiece SwapHash Source # | |
Defined in BtcLsp.Data.Type fromPathPiece :: Text -> Maybe SwapHash # toPathPiece :: SwapHash -> Text # | |
ToJavascript SwapHash Source # | |
Defined in BtcLsp.Data.Type toJavascript :: SwapHash -> Javascript # | |
ToContent (Maybe SwapHash) Source # | |
ToTypedContent (Maybe SwapHash) Source # | |
Defined in BtcLsp.Data.Type toTypedContent :: Maybe SwapHash -> TypedContent # | |
type Rep SwapHash Source # | |
Defined in BtcLsp.Data.Type |