{-# LANGUAGE
OverloadedStrings
, DeriveGeneric
, DuplicateRecordFields
, FlexibleContexts
#-}
module Data.Lightning.Notifications where
import Data.Lightning.Generic
import Data.Lightning.Util
import GHC.Generics
import Data.Aeson.Types
import Data.Text (Text)
data ChannelOpened = ChannelOpened {
ChannelOpened -> Text
___id :: Text
, ChannelOpened -> Int
funding_msat :: Int
, ChannelOpened -> Text
funding_txid :: Text
, ChannelOpened -> Bool
channel_ready :: Bool
} deriving forall x. Rep ChannelOpened x -> ChannelOpened
forall x. ChannelOpened -> Rep ChannelOpened x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChannelOpened x -> ChannelOpened
$cfrom :: forall x. ChannelOpened -> Rep ChannelOpened x
Generic
instance FromJSON ChannelOpened where
parseJSON :: Value -> Parser ChannelOpened
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Key -> Value -> Parser a
singleField Key
"channel_opened"
data ChannelOpenFailed = ChannelOpenFailed {
ChannelOpenFailed -> Text
channel_id :: Text
} deriving forall x. Rep ChannelOpenFailed x -> ChannelOpenFailed
forall x. ChannelOpenFailed -> Rep ChannelOpenFailed x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChannelOpenFailed x -> ChannelOpenFailed
$cfrom :: forall x. ChannelOpenFailed -> Rep ChannelOpenFailed x
Generic
instance FromJSON ChannelOpenFailed where
parseJSON :: Value -> Parser ChannelOpenFailed
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Key -> Value -> Parser a
singleField Key
"channel_open_failed"
data ChannelStateChanged = ChannelStateChanged {
ChannelStateChanged -> Text
peer_id :: Text
, ChannelStateChanged -> Text
channel_id :: Text
, ChannelStateChanged -> Text
short_channel_id :: Text
, ChannelStateChanged -> Text
timestamp :: Text
, ChannelStateChanged -> Text
old_state :: Text
, ChannelStateChanged -> Text
new_state :: Text
, ChannelStateChanged -> Text
cause :: Text
, ChannelStateChanged -> Text
message :: Text
} deriving forall x. Rep ChannelStateChanged x -> ChannelStateChanged
forall x. ChannelStateChanged -> Rep ChannelStateChanged x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChannelStateChanged x -> ChannelStateChanged
$cfrom :: forall x. ChannelStateChanged -> Rep ChannelStateChanged x
Generic
instance FromJSON ChannelStateChanged where
parseJSON :: Value -> Parser ChannelStateChanged
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Key -> Value -> Parser a
singleField Key
"channel_state_changed"
data Connect = Connect {
Connect -> Text
_id :: Text
, Connect -> Text
direction :: Text
, Connect -> Text
address :: Text
} deriving forall x. Rep Connect x -> Connect
forall x. Connect -> Rep Connect x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Connect x -> Connect
$cfrom :: forall x. Connect -> Rep Connect x
Generic
instance FromJSON Connect where
parseJSON :: Value -> Parser Connect
parseJSON = forall a. (Generic a, GFromJSON Zero (Rep a)) => Value -> Parser a
defaultParse
data Disconnect = Disconnect {
Disconnect -> Text
_id :: Text
} deriving forall x. Rep Disconnect x -> Disconnect
forall x. Disconnect -> Rep Disconnect x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Disconnect x -> Disconnect
$cfrom :: forall x. Disconnect -> Rep Disconnect x
Generic
instance FromJSON Disconnect where
parseJSON :: Value -> Parser Disconnect
parseJSON = forall a. (Generic a, GFromJSON Zero (Rep a)) => Value -> Parser a
defaultParse
data InvoiceCreation = InvoiceCreation {
InvoiceCreation -> Text
label :: Text
, InvoiceCreation -> Text
preimage :: Text
, InvoiceCreation -> Int
amount_msat :: Msat
} deriving forall x. Rep InvoiceCreation x -> InvoiceCreation
forall x. InvoiceCreation -> Rep InvoiceCreation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InvoiceCreation x -> InvoiceCreation
$cfrom :: forall x. InvoiceCreation -> Rep InvoiceCreation x
Generic
instance FromJSON InvoiceCreation where
parseJSON :: Value -> Parser InvoiceCreation
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Key -> Value -> Parser a
singleField Key
"invoice_creation"
data Warning = Warning {
Warning -> Text
level :: Text
, Warning -> Text
time :: Text
, Warning -> Text
source :: Text
, Warning -> Text
log :: Text
} deriving forall x. Rep Warning x -> Warning
forall x. Warning -> Rep Warning x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Warning x -> Warning
$cfrom :: forall x. Warning -> Rep Warning x
Generic
instance FromJSON Warning where
parseJSON :: Value -> Parser Warning
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Key -> Value -> Parser a
singleField Key
"warning"
data ForwardEvent = ForwardEvent {
ForwardEvent -> Text
payment_hash :: Text
, ForwardEvent -> Text
in_channel :: Text
, ForwardEvent -> Text
out_channel :: Text
, ForwardEvent -> Int
in_msat :: Msat
, ForwardEvent -> Int
out_msat :: Msat
, ForwardEvent -> Int
fee_msat :: Msat
, ForwardEvent -> Text
status :: Text
, ForwardEvent -> Maybe Int
failcode :: Maybe Int
, ForwardEvent -> Maybe Text
failreason :: Maybe Text
, ForwardEvent -> Double
received_time :: Double
, ForwardEvent -> Maybe Double
resolved_time :: Maybe Double
} deriving forall x. Rep ForwardEvent x -> ForwardEvent
forall x. ForwardEvent -> Rep ForwardEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ForwardEvent x -> ForwardEvent
$cfrom :: forall x. ForwardEvent -> Rep ForwardEvent x
Generic
instance FromJSON ForwardEvent where
parseJSON :: Value -> Parser ForwardEvent
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Key -> Value -> Parser a
singleField Key
"forward_event"
data SendPaySuccess = SendPaySuccess {
SendPaySuccess -> Int
_id :: Int
, SendPaySuccess -> Text
payment_hash :: Text
, SendPaySuccess -> Text
destination :: Text
, SendPaySuccess -> Int
amount_msat :: Msat
, SendPaySuccess -> Int
amount_sent_msat :: Msat
, SendPaySuccess -> Int
created_at :: Int
, SendPaySuccess -> Text
status :: Text
, SendPaySuccess -> Text
payment_preimage :: Text
} deriving forall x. Rep SendPaySuccess x -> SendPaySuccess
forall x. SendPaySuccess -> Rep SendPaySuccess x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendPaySuccess x -> SendPaySuccess
$cfrom :: forall x. SendPaySuccess -> Rep SendPaySuccess x
Generic
instance FromJSON SendPaySuccess where
parseJSON :: Value -> Parser SendPaySuccess
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Key -> Value -> Parser a
singleField Key
"sendpay_success"
data SendPayFailure = SendPayFailure {
SendPayFailure -> Int
code :: Int
, SendPayFailure -> Text
message :: Text
, SendPayFailure -> SPFData
_data :: SPFData
} deriving forall x. Rep SendPayFailure x -> SendPayFailure
forall x. SendPayFailure -> Rep SendPayFailure x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendPayFailure x -> SendPayFailure
$cfrom :: forall x. SendPayFailure -> Rep SendPayFailure x
Generic
instance FromJSON SendPayFailure where
parseJSON :: Value -> Parser SendPayFailure
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Key -> Value -> Parser a
singleField Key
"sendpay_failure"
data SPFData = SPFData {
SPFData -> Int
_id :: Int
, SPFData -> Text
payment_hash :: Text
, SPFData -> Text
destination :: Text
, SPFData -> Int
amount_msat :: Msat
, SPFData -> Int
amount_sent_msat :: Msat
, SPFData -> Int
created_at :: Int
, SPFData -> Text
status :: Text
, SPFData -> Int
erring_index :: Int
, SPFData -> Int
failcode :: Int
, SPFData -> Text
failcodename :: Text
, SPFData -> Text
erring_node :: Text
, SPFData -> Text
erring_channel :: Text
, SPFData -> Int
erring_direction :: Int
} deriving forall x. Rep SPFData x -> SPFData
forall x. SPFData -> Rep SPFData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SPFData x -> SPFData
$cfrom :: forall x. SPFData -> Rep SPFData x
Generic
instance FromJSON SPFData where
parseJSON :: Value -> Parser SPFData
parseJSON = forall a. (Generic a, GFromJSON Zero (Rep a)) => Value -> Parser a
defaultParse
data CoinMovement = CoinMovement {
CoinMovement -> Int
version :: Int
, CoinMovement -> Text
node_id :: Text
, CoinMovement -> Text
__type :: Text
, CoinMovement -> Text
account_id :: Text
, CoinMovement -> Maybe Text
originating_account :: Maybe Text
, CoinMovement -> Maybe Text
txid :: Maybe Text
, CoinMovement -> Maybe Text
utxo_txid :: Maybe Text
, CoinMovement -> Maybe Int
vout :: Maybe Int
, CoinMovement -> Maybe Int
part_id :: Maybe Int
, CoinMovement -> Maybe Text
payment_hash :: Maybe Text
, CoinMovement -> Maybe Int
credit_msat :: Maybe Int
, CoinMovement -> Maybe Int
debit_msat :: Maybe Int
, CoinMovement -> Maybe Int
output_msat :: Maybe Int
, CoinMovement -> Maybe Int
output_count :: Maybe Int
, CoinMovement -> Maybe Int
fees_msat :: Maybe Int
, CoinMovement -> [Text]
tags :: [Text]
, CoinMovement -> Maybe Int
blockheight :: Maybe Int
, CoinMovement -> Int
timestamp :: Int
, CoinMovement -> Text
coin_type :: Text
} deriving (Int -> CoinMovement -> ShowS
[CoinMovement] -> ShowS
CoinMovement -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CoinMovement] -> ShowS
$cshowList :: [CoinMovement] -> ShowS
show :: CoinMovement -> String
$cshow :: CoinMovement -> String
showsPrec :: Int -> CoinMovement -> ShowS
$cshowsPrec :: Int -> CoinMovement -> ShowS
Show, forall x. Rep CoinMovement x -> CoinMovement
forall x. CoinMovement -> Rep CoinMovement x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CoinMovement x -> CoinMovement
$cfrom :: forall x. CoinMovement -> Rep CoinMovement x
Generic)
instance FromJSON CoinMovement where
parseJSON :: Value -> Parser CoinMovement
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Key -> Value -> Parser a
singleField Key
"coin_movement"
data BalanceSnapshot = BalanceSnapshot {
BalanceSnapshot -> [Snapshot]
balance_snapshots :: [Snapshot]
} deriving (forall x. Rep BalanceSnapshot x -> BalanceSnapshot
forall x. BalanceSnapshot -> Rep BalanceSnapshot x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BalanceSnapshot x -> BalanceSnapshot
$cfrom :: forall x. BalanceSnapshot -> Rep BalanceSnapshot x
Generic, Int -> BalanceSnapshot -> ShowS
[BalanceSnapshot] -> ShowS
BalanceSnapshot -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BalanceSnapshot] -> ShowS
$cshowList :: [BalanceSnapshot] -> ShowS
show :: BalanceSnapshot -> String
$cshow :: BalanceSnapshot -> String
showsPrec :: Int -> BalanceSnapshot -> ShowS
$cshowsPrec :: Int -> BalanceSnapshot -> ShowS
Show)
instance FromJSON BalanceSnapshot
data Snapshot = Snapshot {
Snapshot -> Text
node_id :: Text
, Snapshot -> Int
blockheight :: Int
, Snapshot -> Int
timestamp :: Int
, Snapshot -> Saccount
accounts :: Saccount
} deriving (Int -> Snapshot -> ShowS
[Snapshot] -> ShowS
Snapshot -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Snapshot] -> ShowS
$cshowList :: [Snapshot] -> ShowS
show :: Snapshot -> String
$cshow :: Snapshot -> String
showsPrec :: Int -> Snapshot -> ShowS
$cshowsPrec :: Int -> Snapshot -> ShowS
Show, forall x. Rep Snapshot x -> Snapshot
forall x. Snapshot -> Rep Snapshot x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Snapshot x -> Snapshot
$cfrom :: forall x. Snapshot -> Rep Snapshot x
Generic)
instance FromJSON Snapshot
data Saccount = Saccount {
Saccount -> Text
account_id :: Text
, Saccount -> Text
balance :: Text
, Saccount -> Text
coin_type :: Text
} deriving (Int -> Saccount -> ShowS
[Saccount] -> ShowS
Saccount -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Saccount] -> ShowS
$cshowList :: [Saccount] -> ShowS
show :: Saccount -> String
$cshow :: Saccount -> String
showsPrec :: Int -> Saccount -> ShowS
$cshowsPrec :: Int -> Saccount -> ShowS
Show, forall x. Rep Saccount x -> Saccount
forall x. Saccount -> Rep Saccount x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Saccount x -> Saccount
$cfrom :: forall x. Saccount -> Rep Saccount x
Generic)
instance FromJSON Saccount
data BlockAdded = BlockAdded {
BlockAdded -> Text
hash :: Text
, BlockAdded -> Int
height :: Int
} deriving forall x. Rep BlockAdded x -> BlockAdded
forall x. BlockAdded -> Rep BlockAdded x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BlockAdded x -> BlockAdded
$cfrom :: forall x. BlockAdded -> Rep BlockAdded x
Generic
instance FromJSON BlockAdded where
parseJSON :: Value -> Parser BlockAdded
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Key -> Value -> Parser a
singleField Key
"block"
data OpenChannelPeerSigs = OpenChannelPeerSigs {
OpenChannelPeerSigs -> Text
channel_id :: Text
, OpenChannelPeerSigs -> Text
signed_psbt :: Text
} deriving forall x. Rep OpenChannelPeerSigs x -> OpenChannelPeerSigs
forall x. OpenChannelPeerSigs -> Rep OpenChannelPeerSigs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OpenChannelPeerSigs x -> OpenChannelPeerSigs
$cfrom :: forall x. OpenChannelPeerSigs -> Rep OpenChannelPeerSigs x
Generic
instance FromJSON OpenChannelPeerSigs where
parseJSON :: Value -> Parser OpenChannelPeerSigs
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Key -> Value -> Parser a
singleField Key
"openchannel_peer_sigs"