btc-lsp-0.1.0.0: Lightning service provider
Safe HaskellSafe-Inferred
LanguageHaskell2010
Extensions
  • MonoLocalBinds
  • ScopedTypeVariables
  • AllowAmbiguousTypes
  • TypeFamilies
  • OverloadedStrings
  • DataKinds
  • InstanceSigs
  • StandaloneDeriving
  • DeriveGeneric
  • DerivingStrategies
  • DerivingVia
  • TypeSynonymInstances
  • FlexibleContexts
  • FlexibleInstances
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • ExistentialQuantification
  • KindSignatures
  • GeneralizedNewtypeDeriving
  • TupleSections
  • TypeOperators
  • ExplicitNamespaces
  • ExplicitForAll
  • LambdaCase
  • TypeApplications
  • StrictData

BtcLsp.Import.Witch

Documentation

withSource :: source2 -> TryFromException source1 t -> TryFromException source2 t #

withTarget :: forall target2 source target1. TryFromException source target1 -> TryFromException source target2 #

class From source target #

Instances

Instances details
From Int64 RowQty Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Int64 -> RowQty

From Word64 BlkHeight Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Word64 -> BlkHeight

From Word64 Nonce Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Word64 -> Nonce

From Word64 MSat Source # 
Instance details

Defined in BtcLsp.Data.Orphan

Methods

from :: Word64 -> MSat

From Word64 Seconds Source # 
Instance details

Defined in BtcLsp.Data.Orphan

Methods

from :: Word64 -> Seconds

From BlkHash BlockHash Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: BlkHash -> BlockHash

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

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

From NodePubKeyHex Text Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: NodePubKeyHex -> Text

From NodeUriHex Text Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: NodeUriHex -> Text

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 Privacy Privacy Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

Methods

from :: Privacy0 -> Privacy

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 RowQty Int64 Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: RowQty -> Int64

From SigHeaderName ByteString Source # 
Instance details

Defined in BtcLsp.Grpc.Data

From SigHeaderName Text Source # 
Instance details

Defined in BtcLsp.Grpc.Data

Methods

from :: SigHeaderName -> Text

From InQty Natural Source # 
Instance details

Defined in BtcLsp.Math.OnChain

Methods

from :: InQty -> Natural

From OutQty Natural Source # 
Instance details

Defined in BtcLsp.Math.OnChain

Methods

from :: OutQty -> Natural

From FundMoney MSat Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

Methods

from :: FundMoney -> MSat

From LnPubKey NodePubKey Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

Methods

from :: LnPubKey -> NodePubKey

From Nonce Nonce Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

Methods

from :: Nonce -> Nonce0

From Privacy Privacy Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

Methods

from :: Privacy -> Privacy0

From Msat MSat Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

Methods

from :: Msat -> MSat

From MSat Word64 Source # 
Instance details

Defined in BtcLsp.Data.Orphan

Methods

from :: MSat -> Word64

From MSat FundMoney Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

Methods

from :: MSat -> FundMoney

From MSat Msat Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

Methods

from :: MSat -> Msat

From NodePubKey LnPubKey Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

Methods

from :: NodePubKey -> LnPubKey

From PaymentRequest Text Source # 
Instance details

Defined in BtcLsp.Data.Orphan

Methods

from :: PaymentRequest -> Text

From RHash RHashHex Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: RHash -> RHashHex

From Seconds Word64 Source # 
Instance details

Defined in BtcLsp.Data.Orphan

Methods

from :: Seconds -> Word64

From HostName LnHost Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

Methods

from :: HostName -> LnHost

From PortNumber Word32 Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

Methods

from :: PortNumber -> Word32

From PortNumber LnPort Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

Methods

from :: PortNumber -> LnPort

From BlockHash BlkHash Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: BlockHash -> BlkHash

From Text NodePubKeyHex Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Text -> NodePubKeyHex

From Text NodeUriHex Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Text -> NodeUriHex

From Text RHashHex Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Text -> RHashHex

From Text SigHeaderName Source # 
Instance details

Defined in BtcLsp.Grpc.Data

Methods

from :: Text -> SigHeaderName

From Text PaymentRequest Source # 
Instance details

Defined in BtcLsp.Data.Orphan

Methods

from :: Text -> PaymentRequest

From Natural InQty Source # 
Instance details

Defined in BtcLsp.Math.OnChain

Methods

from :: Natural -> InQty

From Natural OutQty Source # 
Instance details

Defined in BtcLsp.Math.OnChain

Methods

from :: Natural -> OutQty

From Int RowQty Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Int -> RowQty

From Word32 (Vout 'Funding) Source # 
Instance details

Defined in BtcLsp.Data.Orphan

Methods

from :: Word32 -> Vout 'Funding

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 Vbyte (Ratio Natural) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Vbyte -> Ratio Natural

From SatPerVbyte (Ratio Natural) Source # 
Instance details

Defined in BtcLsp.Math.OnChain

From FundLnInvoice (LnInvoice 'Fund) Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

From RefundOnChainAddress (UnsafeOnChainAddress 'Refund) 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 OnChainAddress (UnsafeOnChainAddress 'Refund) Source # 
Instance details

Defined in BtcLsp.Grpc.Orphan

From ByteString (TxId 'Funding) Source # 
Instance details

Defined in BtcLsp.Data.Orphan

Methods

from :: ByteString -> TxId 'Funding

From NewAddressResponse (OnChainAddress 'Fund) Source # 
Instance details

Defined in BtcLsp.Data.Smart

Methods

from :: NewAddressResponse -> OnChainAddress 'Fund

From NewAddressResponse (OnChainAddress 'Gain) Source # 
Instance details

Defined in BtcLsp.Data.Smart

Methods

from :: NewAddressResponse -> OnChainAddress 'Gain

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

From Text (UnsafeOnChainAddress mrel) Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Text -> UnsafeOnChainAddress mrel

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

From (Ratio Word64) FeeRate Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Ratio Word64 -> FeeRate

From (Ratio Natural) Vbyte Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: Ratio Natural -> Vbyte

From (Ratio Natural) SatPerVbyte Source # 
Instance details

Defined in BtcLsp.Math.OnChain

From (OnChainAddress 'Fund) FundOnChainAddress Source # 
Instance details

Defined in BtcLsp.Data.Smart

From (OnChainAddress 'Refund) RefundOnChainAddress Source # 
Instance details

Defined in BtcLsp.Data.Smart

From (OnChainAddress mrel) OnChainAddress Source # 
Instance details

Defined in BtcLsp.Data.Smart

From (OnChainAddress mrel) Text Source # 
Instance details

Defined in BtcLsp.Data.Smart

Methods

from :: OnChainAddress mrel -> Text

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

From (UnsafeOnChainAddress mrel) Text Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

from :: UnsafeOnChainAddress 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

class TryFrom source target #

Minimal complete definition

tryFrom

Instances

Instances details
TryFrom Rational FeeRate Source # 
Instance details

Defined in BtcLsp.Data.Type

TryFrom NodeUri NodeUriHex Source # 
Instance details

Defined in BtcLsp.Data.Type

TryFrom ByteString SigHeaderName Source # 
Instance details

Defined in BtcLsp.Grpc.Data

TryFrom NodePubKey NodePubKeyHex Source # 
Instance details

Defined in BtcLsp.Data.Type

TryFrom BlockHeight BlkHeight Source # 
Instance details

Defined in BtcLsp.Data.Type

Methods

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

TryFrom Integer (Vout 'Funding) Source # 
Instance details

Defined in BtcLsp.Data.Orphan

ToBackendKey SqlBackend a => TryFrom Natural (Key a) Source # 
Instance details

Defined in BtcLsp.Data.Orphan

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)

ToBackendKey SqlBackend a => TryFrom (Key a) Natural Source # 
Instance details

Defined in BtcLsp.Data.Orphan

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)

data TryFromException source target #

Constructors

TryFromException source (Maybe SomeException) 

Instances

Instances details
(Show source, Typeable source, Typeable target) => Exception (TryFromException source target) 
Instance details

Defined in Witch.TryFromException

(Show source, Typeable source, Typeable target) => Show (TryFromException source target) 
Instance details

Defined in Witch.TryFromException

Methods

showsPrec :: Int -> TryFromException source target -> ShowS #

show :: TryFromException source target -> String #

showList :: [TryFromException source target] -> ShowS #

from :: forall source target. (From source target, 'False ~ (source == target)) => source -> target Source #

into :: forall target source. (From source target, 'False ~ (source == target)) => source -> target Source #

via :: forall through source target. (From source through, From through target, 'False ~ (source == through), 'False ~ (through == target)) => source -> target Source #

tryFrom :: forall source target. (TryFrom source target, 'False ~ (source == target)) => source -> Either (TryFromException source target) target Source #

tryVia :: forall through source target. (TryFrom source through, TryFrom through target, 'False ~ (source == through), 'False ~ (through == target)) => source -> Either (TryFromException source target) target Source #

composeTry :: forall through source target. ('False ~ (source == through), 'False ~ (through == target)) => (through -> Either (TryFromException through target) target) -> (source -> Either (TryFromException source through) through) -> source -> Either (TryFromException source target) target Source #

composeTryRhs :: forall through source target. ('False ~ (source == through), 'False ~ (through == target)) => (through -> target) -> (source -> Either (TryFromException source through) through) -> source -> Either (TryFromException source target) target Source #

composeTryLhs :: forall through source target. ('False ~ (source == through), 'False ~ (through == target)) => (through -> Either (TryFromException through target) target) -> (source -> through) -> source -> Either (TryFromException source target) target Source #