{-# LANGUAGE
OverloadedStrings
, DeriveGeneric
, DuplicateRecordFields
#-}
module Data.Lightning.Hooks where
import Data.Lightning.Manifest
import Data.Lightning.Generic
import Data.Lightning.Util
import GHC.Generics
import Data.Aeson.Types
import Data.Text (Text)
data Init = Init {
Init -> Object
options :: Object
, Init -> InitConfig
configuration :: InitConfig
} deriving (Msat -> Init -> ShowS
[Init] -> ShowS
Init -> String
forall a.
(Msat -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Init] -> ShowS
$cshowList :: [Init] -> ShowS
show :: Init -> String
$cshow :: Init -> String
showsPrec :: Msat -> Init -> ShowS
$cshowsPrec :: Msat -> Init -> ShowS
Show, forall x. Rep Init x -> Init
forall x. Init -> Rep Init x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Init x -> Init
$cfrom :: forall x. Init -> Rep Init x
Generic)
instance FromJSON Init
data InitConfig = InitConfig {
InitConfig -> Text
lightning5dir :: Text
, InitConfig -> Text
rpc5file :: Text
, InitConfig -> Bool
startup :: Bool
, InitConfig -> Text
network :: Text
, InitConfig -> Features
feature_set :: Features
, InitConfig -> Maybe Addr
proxy :: Maybe Addr
, InitConfig -> Maybe Bool
torv35enabled :: Maybe Bool
, InitConfig -> Maybe Bool
always_use_proxy :: Maybe Bool
} deriving (Msat -> InitConfig -> ShowS
[InitConfig] -> ShowS
InitConfig -> String
forall a.
(Msat -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InitConfig] -> ShowS
$cshowList :: [InitConfig] -> ShowS
show :: InitConfig -> String
$cshow :: InitConfig -> String
showsPrec :: Msat -> InitConfig -> ShowS
$cshowsPrec :: Msat -> InitConfig -> ShowS
Show, forall x. Rep InitConfig x -> InitConfig
forall x. InitConfig -> Rep InitConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InitConfig x -> InitConfig
$cfrom :: forall x. InitConfig -> Rep InitConfig x
Generic)
instance FromJSON InitConfig where
parseJSON :: Value -> Parser InitConfig
parseJSON = forall a. (Generic a, GFromJSON Zero (Rep a)) => Value -> Parser a
defaultParse
data Addr = Addr {
Addr -> Text
_type :: Text
, Addr -> Text
address :: Text
, Addr -> Msat
port :: Int
} deriving (Msat -> Addr -> ShowS
[Addr] -> ShowS
Addr -> String
forall a.
(Msat -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Addr] -> ShowS
$cshowList :: [Addr] -> ShowS
show :: Addr -> String
$cshow :: Addr -> String
showsPrec :: Msat -> Addr -> ShowS
$cshowsPrec :: Msat -> Addr -> ShowS
Show, forall x. Rep Addr x -> Addr
forall x. Addr -> Rep Addr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Addr x -> Addr
$cfrom :: forall x. Addr -> Rep Addr x
Generic)
instance FromJSON Addr where
parseJSON :: Value -> Parser Addr
parseJSON = forall a. (Generic a, GFromJSON Zero (Rep a)) => Value -> Parser a
defaultParse
data PeerConnected = PeerConnected {
PeerConnected -> Text
_id :: Text
, PeerConnected -> Text
direction :: Text
, PeerConnected -> Text
addr :: Text
, PeerConnected -> Text
features :: Text
} deriving forall x. Rep PeerConnected x -> PeerConnected
forall x. PeerConnected -> Rep PeerConnected x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PeerConnected x -> PeerConnected
$cfrom :: forall x. PeerConnected -> Rep PeerConnected x
Generic
instance FromJSON PeerConnected where
parseJSON :: Value -> Parser PeerConnected
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Key -> Value -> Parser a
singleField Key
"peer"
data CommitmentRevocation = CommitmentRevocation {
CommitmentRevocation -> Text
commitment_txid :: Text
, CommitmentRevocation -> Text
penalty_tx :: Text
, CommitmentRevocation -> Text
channel_id :: Text
, CommitmentRevocation -> Msat
commitnum :: Int
} deriving forall x. Rep CommitmentRevocation x -> CommitmentRevocation
forall x. CommitmentRevocation -> Rep CommitmentRevocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CommitmentRevocation x -> CommitmentRevocation
$cfrom :: forall x. CommitmentRevocation -> Rep CommitmentRevocation x
Generic
instance FromJSON CommitmentRevocation
data DbWrite = DbWrite {
DbWrite -> Msat
data_version :: Int
, DbWrite -> [Text]
writes :: [Text]
} deriving forall x. Rep DbWrite x -> DbWrite
forall x. DbWrite -> Rep DbWrite x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DbWrite x -> DbWrite
$cfrom :: forall x. DbWrite -> Rep DbWrite x
Generic
instance FromJSON DbWrite
data InvoicePayment = InvoicePayment {
InvoicePayment -> Text
label :: Text
, InvoicePayment -> Text
preimage :: Text
, InvoicePayment -> Msat
amount_msat :: Msat
} deriving forall x. Rep InvoicePayment x -> InvoicePayment
forall x. InvoicePayment -> Rep InvoicePayment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InvoicePayment x -> InvoicePayment
$cfrom :: forall x. InvoicePayment -> Rep InvoicePayment x
Generic
instance FromJSON InvoicePayment where
parseJSON :: Value -> Parser InvoicePayment
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Key -> Value -> Parser a
singleField Key
"payment"
data OpenChannel = OpenChannel {
OpenChannel -> Text
_id :: Text
, OpenChannel -> Msat
funding_msat :: Msat
, OpenChannel -> Msat
push_msat :: Msat
, OpenChannel -> Msat
dust_limit_msat :: Msat
, OpenChannel -> Msat
max_htlc_value_in_flight_msat :: Msat
, OpenChannel -> Msat
channel_reserve_msat :: Msat
, OpenChannel -> Msat
htlc_minimum_msat :: Msat
, OpenChannel -> Msat
feerate_per_kw :: Int
, OpenChannel -> Msat
to_self_delay :: Int
, OpenChannel -> Msat
max_accepted_htlcs :: Int
, OpenChannel -> Msat
channel_flags :: Int
} deriving forall x. Rep OpenChannel x -> OpenChannel
forall x. OpenChannel -> Rep OpenChannel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OpenChannel x -> OpenChannel
$cfrom :: forall x. OpenChannel -> Rep OpenChannel x
Generic
instance FromJSON OpenChannel where
parseJSON :: Value -> Parser OpenChannel
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Key -> Value -> Parser a
singleField Key
"openchannel"
data OpenChannel2 = OpenChannel2 {
OpenChannel2 -> Text
_id :: Text
, OpenChannel2 -> Text
channel_id :: Text
, OpenChannel2 -> Msat
their_funding_msat :: Msat
, OpenChannel2 -> Msat
dust_limit_msat :: Msat
, OpenChannel2 -> Msat
max_htlc_value_in_flight_msat :: Msat
, OpenChannel2 -> Msat
htlc_minimum_msat :: Msat
, OpenChannel2 -> Msat
funding_feerate_per_kw :: Int
, OpenChannel2 -> Msat
commitment_feerate_per_kw :: Int
, OpenChannel2 -> Msat
feerate_our_max :: Int
, OpenChannel2 -> Msat
feerate_our_min :: Int
, OpenChannel2 -> Msat
to_self_delay :: Int
, OpenChannel2 -> Msat
max_accepted_htlcs :: Int
, OpenChannel2 -> Msat
channel_flags :: Int
, OpenChannel2 -> Msat
locktime :: Int
, OpenChannel2 -> Msat
channel_max_msat :: Msat
, OpenChannel2 -> Msat
requested_lease_msat :: Msat
, OpenChannel2 -> Msat
lease_blockheight_start :: Int
, OpenChannel2 -> Msat
node_blockheight :: Int
} deriving forall x. Rep OpenChannel2 x -> OpenChannel2
forall x. OpenChannel2 -> Rep OpenChannel2 x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OpenChannel2 x -> OpenChannel2
$cfrom :: forall x. OpenChannel2 -> Rep OpenChannel2 x
Generic
instance FromJSON OpenChannel2 where
parseJSON :: Value -> Parser OpenChannel2
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Key -> Value -> Parser a
singleField Key
"openchannel2"
data OpenChannel2Changed = OpenChannel2Changed {
OpenChannel2Changed -> Text
channel_id :: Text
, OpenChannel2Changed -> Text
psbt :: Text
} deriving forall x. Rep OpenChannel2Changed x -> OpenChannel2Changed
forall x. OpenChannel2Changed -> Rep OpenChannel2Changed x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OpenChannel2Changed x -> OpenChannel2Changed
$cfrom :: forall x. OpenChannel2Changed -> Rep OpenChannel2Changed x
Generic
instance FromJSON OpenChannel2Changed where
parseJSON :: Value -> Parser OpenChannel2Changed
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Key -> Value -> Parser a
singleField Key
"openchannel2_changed"
data OpenChannel2Sign = OpenChannel2Sign {
OpenChannel2Sign -> Text
channel_id :: Text
, OpenChannel2Sign -> Text
psbt :: Text
} deriving forall x. Rep OpenChannel2Sign x -> OpenChannel2Sign
forall x. OpenChannel2Sign -> Rep OpenChannel2Sign x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OpenChannel2Sign x -> OpenChannel2Sign
$cfrom :: forall x. OpenChannel2Sign -> Rep OpenChannel2Sign x
Generic
instance FromJSON OpenChannel2Sign where
parseJSON :: Value -> Parser OpenChannel2Sign
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Key -> Value -> Parser a
singleField Key
"openchannel2_sign"
data RbfChannel = RbfChannel {
RbfChannel -> Text
_id :: Text
, RbfChannel -> Text
channel_id :: Text
, RbfChannel -> Msat
their_last_funding_msat :: Msat
, RbfChannel -> Msat
their_funding_msat :: Msat
, RbfChannel -> Msat
our_last_funding_msat :: Msat
, RbfChannel -> Msat
funding_feerate_per_kw :: Int
, RbfChannel -> Msat
feerate_our_max :: Int
, RbfChannel -> Msat
feerate_our_min :: Int
, RbfChannel -> Msat
channel_max_msat :: Msat
, RbfChannel -> Msat
locktime :: Int
, RbfChannel -> Msat
requested_lease_msat :: Msat
} deriving forall x. Rep RbfChannel x -> RbfChannel
forall x. RbfChannel -> Rep RbfChannel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RbfChannel x -> RbfChannel
$cfrom :: forall x. RbfChannel -> Rep RbfChannel x
Generic
instance FromJSON RbfChannel where
parseJSON :: Value -> Parser RbfChannel
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Key -> Value -> Parser a
singleField Key
"rbf_channel"
data HtlcAccepted = HtlcAccepted {
HtlcAccepted -> HtlcOnion
onion :: HtlcOnion
, HtlcAccepted -> Htlc
htlc :: Htlc
, HtlcAccepted -> Text
forward_to :: Text
} deriving forall x. Rep HtlcAccepted x -> HtlcAccepted
forall x. HtlcAccepted -> Rep HtlcAccepted x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HtlcAccepted x -> HtlcAccepted
$cfrom :: forall x. HtlcAccepted -> Rep HtlcAccepted x
Generic
instance FromJSON HtlcAccepted
data HtlcOnion = HtlcOnion {
HtlcOnion -> Text
payload :: Text
, HtlcOnion -> Text
short_channel_id :: Text
, HtlcOnion -> Msat
forward_msat :: Msat
, HtlcOnion -> Msat
outgoing_cltv_value :: Msat
, HtlcOnion -> Text
shared_secret :: Text
, HtlcOnion -> Text
next_ontion :: Text
} deriving forall x. Rep HtlcOnion x -> HtlcOnion
forall x. HtlcOnion -> Rep HtlcOnion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HtlcOnion x -> HtlcOnion
$cfrom :: forall x. HtlcOnion -> Rep HtlcOnion x
Generic
instance FromJSON HtlcOnion
data Htlc = Htlc {
Htlc -> Text
short_channel_id :: Text
, Htlc -> Msat
_id :: Int
, Htlc -> Msat
amount_msat :: Msat
, Htlc -> Msat
cltv_expiry :: Int
, Htlc -> Msat
cltv_expiry_relative :: Int
, Htlc -> Text
payment_hash :: Text
} deriving forall x. Rep Htlc x -> Htlc
forall x. Htlc -> Rep Htlc x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Htlc x -> Htlc
$cfrom :: forall x. Htlc -> Rep Htlc x
Generic
instance FromJSON Htlc where
parseJSON :: Value -> Parser Htlc
parseJSON = forall a. (Generic a, GFromJSON Zero (Rep a)) => Value -> Parser a
defaultParse
data RpcCommand = RpcCommand {
RpcCommand -> Msat
_id :: Int
, RpcCommand -> Text
method :: Text
, RpcCommand -> Value
params :: Value
} deriving forall x. Rep RpcCommand x -> RpcCommand
forall x. RpcCommand -> Rep RpcCommand x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RpcCommand x -> RpcCommand
$cfrom :: forall x. RpcCommand -> Rep RpcCommand x
Generic
instance FromJSON RpcCommand where
parseJSON :: Value -> Parser RpcCommand
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Key -> Value -> Parser a
singleField Key
"rpc_command"
data CustomMsg = CustomMsg {
CustomMsg -> Text
peer_id :: Text
, CustomMsg -> Text
payload :: Text
} deriving forall x. Rep CustomMsg x -> CustomMsg
forall x. CustomMsg -> Rep CustomMsg x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CustomMsg x -> CustomMsg
$cfrom :: forall x. CustomMsg -> Rep CustomMsg x
Generic
instance FromJSON CustomMsg
data OnionMessageRecv = OnionMessageRecv {
OnionMessageRecv -> Text
reply_first_node :: Text
, OnionMessageRecv -> Text
reply_blinding :: Text
, OnionMessageRecv -> [MsgHop]
reply_path :: [MsgHop]
, OnionMessageRecv -> Text
invoice_request :: Text
, OnionMessageRecv -> Text
invoice :: Text
, OnionMessageRecv -> Text
invoice_error :: Text
, OnionMessageRecv -> Value
unknown_fields :: Value
} deriving forall x. Rep OnionMessageRecv x -> OnionMessageRecv
forall x. OnionMessageRecv -> Rep OnionMessageRecv x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OnionMessageRecv x -> OnionMessageRecv
$cfrom :: forall x. OnionMessageRecv -> Rep OnionMessageRecv x
Generic
instance FromJSON OnionMessageRecv
data OnionMessageRecvSecret = OnionMessageRecvSecret {
OnionMessageRecvSecret -> Text
pathsecret :: Text
, OnionMessageRecvSecret -> Text
reply_first_node :: Text
, OnionMessageRecvSecret -> Text
reply_blinding :: Text
, OnionMessageRecvSecret -> [MsgHop]
reply_path :: [MsgHop]
, OnionMessageRecvSecret -> Text
invoice_request :: Text
, OnionMessageRecvSecret -> Text
invoice :: Text
, OnionMessageRecvSecret -> Text
invoice_error :: Text
, OnionMessageRecvSecret -> Value
unknown_fields :: Value
} deriving forall x. Rep OnionMessageRecvSecret x -> OnionMessageRecvSecret
forall x. OnionMessageRecvSecret -> Rep OnionMessageRecvSecret x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OnionMessageRecvSecret x -> OnionMessageRecvSecret
$cfrom :: forall x. OnionMessageRecvSecret -> Rep OnionMessageRecvSecret x
Generic
instance FromJSON OnionMessageRecvSecret
data MsgHop = MsgHop {
MsgHop -> Text
_id :: Text
, MsgHop -> Text
encrypted_recipient_data :: Text
, MsgHop -> Text
blinding :: Text
} deriving forall x. Rep MsgHop x -> MsgHop
forall x. MsgHop -> Rep MsgHop x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MsgHop x -> MsgHop
$cfrom :: forall x. MsgHop -> Rep MsgHop x
Generic
instance FromJSON MsgHop where
parseJSON :: Value -> Parser MsgHop
parseJSON = forall a. (Generic a, GFromJSON Zero (Rep a)) => Value -> Parser a
defaultParse