Looking for feedback on Library, specifically ways to simplify

Hello, I’ve released (my first) Library in Haskell on hackage:
clplug

It works quite well but there are a few things about the interface that make using it seem a bit awkward and I was hoping to get some suggestions to make it better.

Specifically right now the user creates a function within the PluginMonad:

type PluginMonad a = ReaderT Plug (StateT a IO)

Within that monad you have access to other functions defined with access to the plug reader and you have access to the polymorphic state you define, but it seems like it forces too much. What if you want more environment variables? It seems like the second Monad, StateT within the reader, could be fully general, I’ve seen other libraries (Servant) use the concept of hoisting, but given how I created the plugin function (Control/Plugin) I can’t quite understand how I would initialize the Conduit (runPlugin | line27) within a polymorphic monad.

Another thing is when I have been using it I have been using ViewPatterns:

Just (Res (fromJSON -> Success funds@(Funds{}) ) _) <- lightningCli listfunds

But I am unsure as to what would happen (it never does in practice) if the pattern match failed or if/how it is possible to define specify that. Sometimes nothing happening is fine but other times a response is required.

If you take some time to read through the library any have any comments about form or function that come to mind, they would be much appreciated. I’ve created a few plugins (executable projects created using the library) that may be useful to see how it is used but I can only link one :stuck_out_tongue: : Summarize Some Info

1 Like

I don’t have a clue what it is about, so from the cursory glance…

  1. The Readme states that you should create a manifest… using Aeson functions. This forces the user to know library internals and work with it using some other library. The good way to provide this would be filling out a Haskell type. Maybe you have it in the Manifest module, but then you should update docs (:
  2. Some types are using String fields while some use Text. Stick to the Text by default.
  3. Control.Client and Control.Plugin names are too generic. If anything, inject a Lightning in there, like you did with the Data.* modules. Even better - drop both Control and Data and just use Lightning.* prefix everywhere.
  4. PluginMonad a forces the user to deal with StateT, which may be not the option that they’d prefer. If you don’t need that for implementation purposes, remove it and let the users bring their own state wrapper (e.g. StateT userState PluginMonad). Even better - make your ReaderT wrapper optional, so the users can run your (MonadReader env m, HasLightning env) functions without extra layers.
  5. You don’t need to announce that a plugin environment is a Monad in a type. myPlugin :: Plugin a has just as much information.
  6. Looks like Generic, and Utils modules can be merged into Internal. And the type aliases you define bring almost no value since they aren’t enforced and have no documentation attached. Also, they don’t seem to be used much (I’ve seen “msat” field somewhere that is Int instead of Msat).

PS(a): I’d recommend publishing would-be packages on a public repository first, undergoing a review and fixing things, and then cut a release. The Hackage is not a code repository and lots of small tweaks wastes common resources. At the same time, project tools can grab package contents from git repos directly, without mediating updates with Hackage.

2 Likes

Another thing I would like to ask is if my use of the conduit library is worth it. Originally the conduit started from stdin and progressed to stdout but because there is not a 1:1 relationship between I had to move to using the stdout handle directly for responses. So it is a bit of a hybrid and I’m not sure it’s benefiting from using conduit.

Thanks for the comments wix. I think point 3 is especially interesting, but the implementation is confusing. What is the equivalent of (evalStateT s) . (runReaderT r) to embed the app if the whole monad is polymorphic!?

I’m not quite understand that “embedding the app” means here. Can you post some code that demonstrates it?

The idea of the Library is to make plugins: an executable that communicates with a main process over stdin/stdout. The Library is meant to handle the implementation details of ‘being a plugin’ so the user can just think about the feature. In sudo-code (link to actual plugin fn)

plugin configuration startup app = do 
    r <- <handle initialize, create reader>
    s <- runReaderT startup r
    `evalState` s . `runReader` r . forever . conduit . app

The app function gets called every time data gets sent over stdin. I mean the app is embedded within the reader and state initialization during startup. Having that polymorphic state has been useful but in practice it’s mostly been holding a database Connection which could be in a reader.

1 Like

The question is: if I didn’t do this little dipsydo where the return value of the startup function becomes the initial state of the stateT and fully defines the monad stack to ReaderT Plug (StateT a IO), how would the operating context be initialized and carried between calls? It may not be possible? Anyhow I pursue the working not the perfect.

Because of the feedback I discovered that all the functionality can be run under ConstraintKind: type Plugin m = (MonadReader Plug m, MonadIO m) and am refactoring to live under a new Clplug namespace. Thanks

1 Like

I think you can let the plugin provide the runner for the app and extricate yourself from the question of state.

plugin config startup app =
  startup config $
    wrapWrapWrap app -- do what you need to run the app for each request

example :: IO () -- they appear to be self-contained?.. 🤔
example = plugin "hello" runner app

runner :: Config -> (Req -> App) -> IO ()
runner config wrappedApp = do
  db <- connect config
  let env = (config, True)
  runSuperFancy wrappedApp env

app
  :: PluginReq -- your business
  -> SuperFancy '[Effectfully, Effectful, Effects] -- not your business
app req = do
  result <- consultDB req
  respond req result

BTW, can you have more than one plugin?

Yes they are self-contained meaning the one function defines one executable program

main = plugin manifest start app

that can be attached to a core lightning daemon to add functionality like react to payment route or add rpc interface command. The details of what this attaches to can be found here: Core Lightning Plugin Documentation.

I need to consider more if your that construct will work. It pushes more complexity onto the user which makes sense as an unavoidable tradeoff. Perhaps I will provide a couple different options, ie plugin & pluginFree

Ah… So the wrapper provides some control loop and the app is running inside it.
I think you really should avoid forcing user into a particular environment.

import App qualified

main = do
  appWorld <- App.initialize :: IO App.Whatevers
  plugin {- ... all the control loop necessities ... -} (App.run appWorld)

initialize :: IO Whatevers
initialize = getCurrentWhatever "app"

run :: Whatevers -> Req -> IO ()
run env req = runFancyT (handle req) env

handle :: Req -> Fancy ()

If the application needs to know something about the core loop and its specifics you can put that in the Req type:

handle :: Req -> Fancy ()
handle req = do
  print (req.currentRequestId, req.manifest.instanceName)

Trust the user that they know how to runReaderT. Otherwise you’d be taxing everyone else, who know how to run it, but want some other wrapper.

Cool, I was able to get that working construct working :+1: This little plugin creates a new rpc command and runs in stateT but think that means any runner will work.

{-# LANGUAGE 
    OverloadedStrings 
  , FlexibleContexts
    #-}
module Main (main) where

import Clplug
import Control.Concurrent
import Data.Aeson 
import Data.Text (Text)
import Control.Monad.State

manifest = object [
      "dynamic" .= True
    , "rpcmethods" .= [
         RpcMethod "hopper" "" "show state" Nothing False
       ]
    ]

app (Just i, "hopper", _ ) = do 
  s <- get
  liftIO $ respond s i

main :: IO ()
main = do 
  i <- initialize manifest
  evalStateT (insertApp app) "free"
  threadDelay maxBound 

Refactoring / redesigning in haskell is a pleasure. This way lost the convenience reader that made the rpcClient wrapper more convenient but cool it works. initialize

I see parts of JSON-RPC2 implemented in the code. Have you looked at the json-rpc package? It works with conduit streams too.

I was able to get a working executable using json-rpc but could not use filter feature so ended up keeping the manual conduitT code and dependencies. Main can be created with plugInit & plugRun within user monad:

main = do 
   (init', cli') <- plugInit m
   plugRun . (`runReaderT` t).(`evalStateT` s') $ 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  

I wanted to move receiveRequest into plugRun but when doing so ran into errors trying to initialize:

plugRun app = runNoLoggingT.forever.jsonrpc $ do 
    Just req <- receiveRequest 
    app req

-- XXX No instance for (Control.Monad.IO.Unlift.MonadUnliftIO(StateT ...
main = 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)
main = do 
     (init', cli') <- plugInit m
     plugRun.(`evalStateT` s) $ app cli'
     where 
     app cli (Request V2 "clplug2" _ cid) = undefined 

new repo (test/Main.hs)

You’d better put some spaces around those (.)s, given OverloadedRecordDot is a thing now.