{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module BtcLsp.Grpc.Orphan
( intoProto,
fromProto,
)
where
import BtcLsp.Data.Kind
import BtcLsp.Data.Orphan ()
import BtcLsp.Data.Type
import BtcLsp.Import.External
import Data.ProtoLens.Field
import Data.ProtoLens.Message
import qualified LndClient as Lnd
import qualified Proto.BtcLsp.Data.HighLevel as Proto
import qualified Proto.BtcLsp.Data.HighLevel_Fields as Proto
import qualified Proto.BtcLsp.Data.LowLevel as Proto
import qualified Proto.BtcLsp.Data.LowLevel_Fields as LowLevel
import qualified Witch
fromProto ::
forall proto through haskell.
( HasField proto "val" through,
From through haskell,
'False ~ (through == haskell)
) =>
proto ->
haskell
fromProto :: forall proto through haskell.
(HasField proto "val" through, From through haskell,
'False ~ (through == haskell)) =>
proto -> haskell
fromProto =
through -> haskell
forall source target.
(From source target, 'False ~ (source == target)) =>
source -> target
from
(through -> haskell) -> (proto -> through) -> proto -> haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (proto -> Getting through proto through -> through
forall s a. s -> Getting a s a -> a
^. forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
field @"val")
intoProto ::
forall proto through haskell.
( Message proto,
HasField proto "val" through,
From haskell through,
'False ~ (haskell == through)
) =>
haskell ->
proto
intoProto :: forall proto through haskell.
(Message proto, HasField proto "val" through, From haskell through,
'False ~ (haskell == through)) =>
haskell -> proto
intoProto haskell
x =
proto
forall msg. Message msg => msg
defMessage
proto -> (proto -> proto) -> proto
forall a b. a -> (a -> b) -> b
& forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
field @"val" ((through -> Identity through) -> proto -> Identity proto)
-> through -> proto -> proto
forall s t a b. ASetter s t a b -> b -> s -> t
.~ haskell -> through
forall source target.
(From source target, 'False ~ (source == target)) =>
source -> target
from haskell
x
instance From Proto.Nonce Nonce where
from :: Nonce -> Nonce
from = Nonce -> Nonce
forall proto through haskell.
(HasField proto "val" through, From through haskell,
'False ~ (through == haskell)) =>
proto -> haskell
fromProto
instance From Nonce Proto.Nonce where
from :: Nonce -> Nonce
from = Nonce -> Nonce
forall proto through haskell.
(Message proto, HasField proto "val" through, From haskell through,
'False ~ (haskell == through)) =>
haskell -> proto
intoProto
instance From Proto.LnPubKey NodePubKey where
from :: LnPubKey -> NodePubKey
from =
ByteString -> NodePubKey
coerce (ByteString -> NodePubKey)
-> (LnPubKey -> ByteString) -> LnPubKey -> NodePubKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LnPubKey -> Getting ByteString LnPubKey ByteString -> ByteString
forall s a. s -> Getting a s a -> a
^. Getting ByteString LnPubKey ByteString
forall (f :: * -> *) s a.
(Functor f, HasField s "val" a) =>
LensLike' f s a
Proto.val)
instance From NodePubKey Proto.LnPubKey where
from :: NodePubKey -> LnPubKey
from NodePubKey
x =
LnPubKey
forall msg. Message msg => msg
defMessage
LnPubKey -> (LnPubKey -> LnPubKey) -> LnPubKey
forall a b. a -> (a -> b) -> b
& LensLike' Identity LnPubKey ByteString
forall (f :: * -> *) s a.
(Functor f, HasField s "val" a) =>
LensLike' f s a
Proto.val LensLike' Identity LnPubKey ByteString
-> ByteString -> LnPubKey -> LnPubKey
forall s t a b. ASetter s t a b -> b -> s -> t
.~ NodePubKey -> ByteString
coerce NodePubKey
x
instance From Proto.LnInvoice (LnInvoice mrel) where
from :: LnInvoice -> LnInvoice mrel
from =
forall through source target.
(From source through, From through target,
'False ~ (source == through), 'False ~ (through == target)) =>
source -> target
via @Lnd.PaymentRequest (Text -> LnInvoice mrel)
-> (LnInvoice -> Text) -> LnInvoice -> LnInvoice mrel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LnInvoice -> Getting Text LnInvoice Text -> Text
forall s a. s -> Getting a s a -> a
^. Getting Text LnInvoice Text
forall (f :: * -> *) s a.
(Functor f, HasField s "val" a) =>
LensLike' f s a
Proto.val)
instance From (LnInvoice mrel) Proto.LnInvoice where
from :: LnInvoice mrel -> LnInvoice
from LnInvoice mrel
x =
LnInvoice
forall msg. Message msg => msg
defMessage
LnInvoice -> (LnInvoice -> LnInvoice) -> LnInvoice
forall a b. a -> (a -> b) -> b
& LensLike' Identity LnInvoice Text
forall (f :: * -> *) s a.
(Functor f, HasField s "val" a) =>
LensLike' f s a
Proto.val LensLike' Identity LnInvoice Text -> Text -> LnInvoice -> LnInvoice
forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall through source target.
(From source through, From through target,
'False ~ (source == through), 'False ~ (through == target)) =>
source -> target
via @Lnd.PaymentRequest LnInvoice mrel
x
instance From Proto.FundLnInvoice (LnInvoice 'Fund) where
from :: FundLnInvoice -> LnInvoice 'Fund
from = FundLnInvoice -> LnInvoice 'Fund
forall proto through haskell.
(HasField proto "val" through, From through haskell,
'False ~ (through == haskell)) =>
proto -> haskell
fromProto
instance From (LnInvoice 'Fund) Proto.FundLnInvoice where
from :: LnInvoice 'Fund -> FundLnInvoice
from = LnInvoice 'Fund -> FundLnInvoice
forall proto through haskell.
(Message proto, HasField proto "val" through, From haskell through,
'False ~ (haskell == through)) =>
haskell -> proto
intoProto
instance From Proto.OnChainAddress (UnsafeOnChainAddress 'Refund) where
from :: OnChainAddress -> UnsafeOnChainAddress 'Refund
from = OnChainAddress -> UnsafeOnChainAddress 'Refund
forall proto through haskell.
(HasField proto "val" through, From through haskell,
'False ~ (through == haskell)) =>
proto -> haskell
fromProto
instance From Proto.RefundOnChainAddress (UnsafeOnChainAddress 'Refund) where
from :: RefundOnChainAddress -> UnsafeOnChainAddress 'Refund
from = RefundOnChainAddress -> UnsafeOnChainAddress 'Refund
forall proto through haskell.
(HasField proto "val" through, From through haskell,
'False ~ (through == haskell)) =>
proto -> haskell
fromProto
instance From Proto.Privacy Privacy where
from :: Privacy -> Privacy
from = Int -> Privacy
forall a. Enum a => Int -> a
toEnum (Int -> Privacy) -> (Privacy -> Int) -> Privacy -> Privacy
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Privacy -> Int
forall a. Enum a => a -> Int
fromEnum
instance From Privacy Proto.Privacy where
from :: Privacy -> Privacy
from = Int -> Privacy
forall a. Enum a => Int -> a
toEnum (Int -> Privacy) -> (Privacy -> Int) -> Privacy -> Privacy
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Privacy -> Int
forall a. Enum a => a -> Int
fromEnum
instance From Proto.Msat MSat where
from :: Msat -> MSat
from = Msat -> MSat
forall proto through haskell.
(HasField proto "val" through, From through haskell,
'False ~ (through == haskell)) =>
proto -> haskell
fromProto
instance From MSat Proto.Msat where
from :: MSat -> Msat
from = MSat -> Msat
forall proto through haskell.
(Message proto, HasField proto "val" through, From haskell through,
'False ~ (haskell == through)) =>
haskell -> proto
intoProto
instance From Proto.FundMoney MSat where
from :: FundMoney -> MSat
from = FundMoney -> MSat
forall proto through haskell.
(HasField proto "val" through, From through haskell,
'False ~ (through == haskell)) =>
proto -> haskell
fromProto
instance From MSat Proto.FundMoney where
from :: MSat -> FundMoney
from = MSat -> FundMoney
forall proto through haskell.
(Message proto, HasField proto "val" through, From haskell through,
'False ~ (haskell == through)) =>
haskell -> proto
intoProto
deriving stock instance Eq CompressMode
deriving stock instance Generic CompressMode
instance FromJSON CompressMode
instance From PortNumber Word32 where
from :: PortNumber -> Word32
from = PortNumber -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From PortNumber Proto.LnPort where
from :: PortNumber -> LnPort
from = PortNumber -> LnPort
forall proto through haskell.
(Message proto, HasField proto "val" through, From haskell through,
'False ~ (haskell == through)) =>
haskell -> proto
intoProto
instance From HostName Proto.LnHost where
from :: HostName -> LnHost
from = HostName -> LnHost
forall proto through haskell.
(Message proto, HasField proto "val" through, From haskell through,
'False ~ (haskell == through)) =>
haskell -> proto
intoProto
instance From (Money owner btcl mrel) Proto.Msat where
from :: Money owner btcl mrel -> Msat
from = Money owner btcl mrel -> Msat
forall proto through haskell.
(Message proto, HasField proto "val" through, From haskell through,
'False ~ (haskell == through)) =>
haskell -> proto
intoProto
instance From (Money 'Usr btcl 'Fund) Proto.LocalBalance where
from :: Money 'Usr btcl 'Fund -> LocalBalance
from = Money 'Usr btcl 'Fund -> LocalBalance
forall proto through haskell.
(Message proto, HasField proto "val" through, From haskell through,
'False ~ (haskell == through)) =>
haskell -> proto
intoProto
instance From (Money 'Lsp btcl 'Gain) Proto.FeeMoney where
from :: Money 'Lsp btcl 'Gain -> FeeMoney
from = Money 'Lsp btcl 'Gain -> FeeMoney
forall proto through haskell.
(Message proto, HasField proto "val" through, From haskell through,
'False ~ (haskell == through)) =>
haskell -> proto
intoProto
instance From FeeRate Proto.Urational where
from :: FeeRate -> Urational
from (FeeRate Ratio Word64
x) =
Urational
forall msg. Message msg => msg
defMessage
Urational -> (Urational -> Urational) -> Urational
forall a b. a -> (a -> b) -> b
& LensLike' Identity Urational Word64
forall (f :: * -> *) s a.
(Functor f, HasField s "numerator" a) =>
LensLike' f s a
LowLevel.numerator LensLike' Identity Urational Word64
-> Word64 -> Urational -> Urational
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Ratio Word64 -> Word64
forall a. Ratio a -> a
numerator Ratio Word64
x
Urational -> (Urational -> Urational) -> Urational
forall a b. a -> (a -> b) -> b
& LensLike' Identity Urational Word64
forall (f :: * -> *) s a.
(Functor f, HasField s "denominator" a) =>
LensLike' f s a
LowLevel.denominator LensLike' Identity Urational Word64
-> Word64 -> Urational -> Urational
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Ratio Word64 -> Word64
forall a. Ratio a -> a
denominator Ratio Word64
x
instance From FeeRate Proto.FeeRate where
from :: FeeRate -> FeeRate
from = FeeRate -> FeeRate
forall proto through haskell.
(Message proto, HasField proto "val" through, From haskell through,
'False ~ (haskell == through)) =>
haskell -> proto
intoProto