{-# LANGUAGE OverloadedStrings , BlockArguments , LambdaCase #-} module Main (main) where import Lightning.Plugin import Lightning.Manifest import Data.Aeson import Network.JSONRPC import Control.Monad.State import Control.Monad.Reader import Data.Text (Text) m :: Value m = genManifest True [] [RpcMethod "clplug2" "" "" Nothing False] [] [] [] main :: IO () --main = runNoLoggingT plugin --main = plugInit m do -- Just (Request V2 "clplug2" _ rid) <- lift receiveRequest -- Just (Right fo) <- sendRequest $ C "getinfo" (object []) -- lift.sendResponse $ Response V2 (toJSON fo) rid main = main1 main1 :: IO () main1 = do (init', cli') <- plugInit m _ <- liftIO $ pure () -- start services plugRun . (`runReaderT` ("test"::Text)).(`evalStateT` init') $ do Just req' <- lift.lift $ receiveRequest app cli' req' where app cli' (Request V2 "clplug2" _ cid) = do _ <- get _ <- lift ask re <- liftIO $ cli' "getinfo" (Just (object [])) (Just (object ["alias".=True])) lift.lift.sendResponse $ Response V2 re cid -- main2 :: IO () -- XXX change plugRun to bind from receiveRequest -- main2 = do -- (init', cli') <- plugInit m -- plugRun (app cli') -- where -- app cli (Request V2 "clplug2" _ cid) = do -- re <- liftIO $ cli -- "getinfo" -- (Just (object [])) -- (Just (object ["alias".=True])) -- sendResponse $ Response V2 re cid -- XXX No instance for (Control.Monad.IO.Unlift.MonadUnliftIO (StateT ... -- main3 :: IO () -- main3 = do -- (init', cli') <- plugInit m -- (flip evalStateT init'). plugRun $ app cli' -- where -- app cli (Request V2 "clplug2" _ cid) = undefined -- XXX Can't match StateT with (Request -> a) -- main4 :: IO () -- main4 = do -- (init', cli') <- plugInit m -- plugRun $ evalStateT (app cli') init' -- where -- app cli (Request V2 "clplug2" _ cid) = undefined