{-# LANGUAGE DeriveGeneric , DuplicateRecordFields #-} module Data.Lightning.Manifest where import GHC.Generics import Data.Lightning.Generic import Data.Aeson import Data.Text (Text) type Manifest = Value data Option = Option { Option -> Text name :: Text , Option -> Text _type :: Text , Option -> Text _default :: Text , Option -> Text description :: Text , Option -> Bool deprecated :: Bool } deriving forall x. Rep Option x -> Option forall x. Option -> Rep Option x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep Option x -> Option $cfrom :: forall x. Option -> Rep Option x Generic instance ToJSON Option where toJSON :: Option -> Value toJSON = forall a. (Generic a, GToJSON' Value Zero (Rep a)) => Options -> a -> Value genericToJSON Options defaultOptions{fieldLabelModifier :: String -> String fieldLabelModifier = forall a. (a -> Bool) -> [a] -> [a] dropWhile (forall a. Eq a => a -> a -> Bool ==Char '_')} data RpcMethod = RpcMethod { RpcMethod -> Text name :: Text , RpcMethod -> Text usage :: Text , RpcMethod -> Text description :: Text , RpcMethod -> Maybe Text long_description :: Maybe Text , RpcMethod -> Bool deprecated :: Bool } deriving forall x. Rep RpcMethod x -> RpcMethod forall x. RpcMethod -> Rep RpcMethod x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep RpcMethod x -> RpcMethod $cfrom :: forall x. RpcMethod -> Rep RpcMethod x Generic instance ToJSON RpcMethod where toJSON :: RpcMethod -> Value toJSON = forall a. (Generic a, GToJSON' Value Zero (Rep a)) => Options -> a -> Value genericToJSON Options defaultOptions{omitNothingFields :: Bool omitNothingFields = Bool True} data Hook = Hook { Hook -> Text name :: Text , Hook -> Maybe Value before :: Maybe Value } deriving forall x. Rep Hook x -> Hook forall x. Hook -> Rep Hook x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep Hook x -> Hook $cfrom :: forall x. Hook -> Rep Hook x Generic instance ToJSON Hook where toJSON :: Hook -> Value toJSON = forall a. (Generic a, GToJSON' Value Zero (Rep a)) => Options -> a -> Value genericToJSON Options defaultOptions{omitNothingFields :: Bool omitNothingFields = Bool True} data Notification = Notification { Notification -> Text __method :: Text } deriving forall x. Rep Notification x -> Notification forall x. Notification -> Rep Notification x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep Notification x -> Notification $cfrom :: forall x. Notification -> Rep Notification x Generic instance ToJSON Notification where toJSON :: Notification -> Value toJSON = forall a. (Generic a, GToJSON' Value Zero (Rep a)) => Options -> a -> Value genericToJSON Options defaultOptions{fieldLabelModifier :: String -> String fieldLabelModifier = forall a. (a -> Bool) -> [a] -> [a] dropWhile (forall a. Eq a => a -> a -> Bool ==Char '_')} data Features = Features { Features -> String __init :: String , Features -> String node :: String , Features -> String channel :: String , Features -> String invoice :: String } deriving (forall x. Rep Features x -> Features forall x. Features -> Rep Features x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep Features x -> Features $cfrom :: forall x. Features -> Rep Features x Generic, Int -> Features -> String -> String [Features] -> String -> String Features -> String forall a. (Int -> a -> String -> String) -> (a -> String) -> ([a] -> String -> String) -> Show a showList :: [Features] -> String -> String $cshowList :: [Features] -> String -> String show :: Features -> String $cshow :: Features -> String showsPrec :: Int -> Features -> String -> String $cshowsPrec :: Int -> Features -> String -> String Show) instance ToJSON Features instance FromJSON Features where parseJSON :: Value -> Parser Features parseJSON = forall a. (Generic a, GFromJSON Zero (Rep a)) => Value -> Parser a defaultParse