KingoftheHomeless/in-other-words

a few questions that came up while implementing readline-in-other-words

Closed this issue · 4 comments

First off: I like this effect system a lot, I think this is a very promising direction.

I have implemented readline-in-other-words for providing a haskeline compatible Readline effect utilizing the InputT monad transformer as a novel monad transformer, and was able to do everything reasonably well using the guides on the wiki, but have a few lingering questions:

  • I don't understand why there is a Carrier m constraint on most interpreters even when it isn't strictly necessary. I was able to compile
    main :: IO ()
    main = runM $
      runReadline defaultSettings $
        handleInterrupt (outputStrLn "Interrupt!" *> repl) $
          withInterrupt $ do
            mline <- getInputLine "> "
            case mline of
              Nothing -> pure ()
              Just line -> outputStrLn line *> repl
    
    even when runReadline didn't have any of the threading/Carrier constraints. I think I will probably add them for consistency, but it feels like a mistake to have extraneous constraints unless they are needed for type safety in a way that I don't understand.
  • BaseControl's constructor isn't exported except through internal modules. This was an obstacle when trying to write a ThreadsEff InputT (BaseControl b) instance because InputT doesn't conform to MonadBaseControl thus I couldn't use threadBaseControlViaClass but it still admits an implementation via withRunInBase. This ended up not being a problem because I implemented the threading constraints on ReadlineC anyways, and then just implemented a MonadBaseControl instance for ReadlineC, but it might be nice to expose it anyways for similar circumstances if that would be possible
  • I constrain the base monad with MonadIO m in
    runReadline ::
      (MonadIO m, MonadMask m) =>
      H.Settings m ->
      ReadlineInterruptC m a ->
      m a
    runReadline settings = H.runInputT settings . unReadlineInterruptC
    
    because runInputT has it as a constraint. Similarly I require that constraint for my Carrier instance because most of the actions require it. I don't see any instances where MonadIO constrains the base monad the main library, instead it seems to use Eff (Embed IO) m when it needs to accomplish something similar. I don't see how to perform this conversion. If that is possible, is a similar conversion possible for MonadMask?
  • I ended up implementing ThreadsEff instances on one of my carrier newtypes ReadlineC instead of InputT directly to avoid orphan instances. Its still ergonomic because I can coerce between the two different carriers, but doesn't follow the main pattern which is for the threading constraints to be defined directly on the monad transformers. Do you have an opinion on this? In general it seems that libraries outside of the main one will always have this problem because the only way orphans are avoided in the main library is by defining them in the same module as the class.
  • Naming: I kind of hope packages for this library adopt the *-in-other-words naming scheme rather than the traditional in-other-words-* naming scheme for integration package (e.g. polysemy-readline) because it reads better in English grammar

Oof, this ended up a lot longer than I initially expected! If you made it this far, I'll add that I would appreciate it if you reviewed my library before I publish it on hackage: https://github.com/lehmacdj/readline-in-other-words/blob/main/src/Control/Effect/Readline/Internal.hs

Thanks!

I appreciate your interest and contributions! in-other-words has some significant differences in priorities compared to most other effect systems (most notably, expressivity first), and I'm always interested to see what people's experiences are with the library because of that.

I'll definitely take an in-depth look at your library once I have the time, but I can answer the questions you asked right now:

  • The constraints placed on the interpreters of in-other-words reflect the constraints needed for the Carrier instance of the effect carrier the interpreter uses.
    This is done for two reasons:

    • It advertises the constraints needed to use the interpreter in practice at the interpreter ("in practice" because if you're not using the Carrier instance of the effect carrier, why are you running the interpreter at all?)
      If the constraints were not placed on the interpreter, then the user would be forced to manually figure out the constraints needed.

      • In the best case, the user would have to look at the carrier newtype of the interpreter, find the documentation of its Carrier instance, and look at the constraints involved.
        This would be very annoying.

      • In the worst case, the carrier is a type synonym for a CompositionC and the exact constraints are not written anywhere, but need to be deduced from the carrier stack involved.
        This would be absolutely horrible.

    • It catches any compile time errors caused by the missing constraints early, in a centralized spot -- the use of the interpreter -- rather than at whatever point the Carrier instance is attempted to be used. This makes for better UX regarding error messages -- and in-other-words needs all it can get in that area.

  • Good point. I will never expose BaseControl's constructor -- too complex, and I may plausibly want to change it in the future -- however, I could add more utilities for threading BaseControl. I should definitely add threadBaseControlViaUnlift -- Unlift is one of the easiest effects to manually write a ThreadsEff instance for (when it's possible), and is strictly stronger than BaseControl. The reason I didn't have threadBaseControlViaUnlift earlier was I figured people would just thread Unlift using threadUnliftViaClass, in which case threadBaseControlViaClass could also be used -- but this a concrete use-case where that's not the case.

  • This is a tough one. Typically, you would be able to make the kind of conversions you're talking about by using Effly, but that's not possible in this case as InputT is abstract, so you can't transform the monad InputT is acting on through coerce. You could use Effly within ReadlineC as the carrier InputT transforms, but then the instances of ReadlineC will be dictated by that of Effly's, which you don't want.

    One of the few solutions I can see for the moment is rather brutal -- define a newtype wrapper that is a limited version of Effly with only the special instance for MonadIO (and MonadMask if you want to convert that too), use that in ReadlineC as the monad InputT transforms, and then write a manual MonadIO (and MonadMask) instance for ReadlineC to circumvent the special instance that your new newtype has.

    It would look something like this:

    newtype EfflyIO m a = EfflyIO { unEfflyIO :: m a }
      deriving ( ... ) -- all the standard chaff, including Carrier, EXCEPT MonadIO
    
    deriving via Effly m instance Eff (Embed IO) m => MonadIO (EfflyIO m)
    
    newtype ReadlineC m a = ReadlineC {unReadlineC :: H.InputT (EfflyIO m) a}
      deriving ( ... ) -- all the standard chaff, EXCEPT MonadIO and Carrier
    
    instance MonadIO m => MonadIO (ReadLineC m) where
      liftIO = ReadlineC . lift . lift . liftIO
    
    instance
      ( Eff (Embed IO) m,
        MonadMask m,
        Threads H.InputT (Prims m)
      ) => Carrier (ReadlineC m) where
      ...

    This gets even harder if you want to do the same conversion for MonadMask, as the manually written MonadMask (ReadlineC m) instance will be a pain.

    In my eyes, it's ok to leave the MonadMask constraint -- delegating to effects allows for additional flexibility, but this comes at the cost of forcing users to add interpreters for them. Placing Eff (Embed IO) m as constraints on interpreters/carriers instead of MonadIO m is almost entirely "free" in the sense of overhead for the user, as runM -- needed to finalize a carrier stack -- automatically provides an Embed effect for the final monad. (In the rare case the final monad is not IO but some other MonadIO, people can use embedToMonadIO)
    This is not the case for the Mask/Bracket effects, which will need to be explicitly interpreted using bracketToIO/maskToIO. This is why in the library whenever I have an effect interpreter that needs to do MonadMask/MonadCatch stuff, I offer two variants of that interpreter: one that uses those classes directly (e.g. errorToIO, writerToIO) and one variant that relies on corresponding effects (e.g. errorToErrorIO, writerToBracket).

  • Yeah, this is a shame. I don't like doing ThreadsEff on carriers directly, because a carrier corresponds to an interpreter, and the ability for a transformer to thread an effect should morally be interpreter-agnostic.
    My preference would be to define a non-carrier newtype of InputT purely to gain ownership, define ThreadsEff instances for that newtype, and then use it as the underlying monad transformer for ReadlineC and other carriers you define rather than InputT directly. But that's a lot of ritual for not much benefit.

  • I don't have strong feelings one way or the other! What matters to me is discoverability, but it seems like Hackage search deals equally well with suffixes as prefixes.

@lehmacdj Turns out I was wrong about InputT being abstract messing things up! You can still transform the transformed monad using coerce -- GHC only restricts uses of coerce that would effectively act as using the newtype's constructor or pattern matching upon it.

This means that you can solve your problem via Effly quite easily, like this:

-- Note: Effly/EfflyIO no longer part of ReadlineC!
newtype ReadlineC m a = ReadlineC { unReadlineC :: ReadlineT m a }
  deriving (...) -- All the standard chaff, INCLUDING MonadIO and MonadMask, except Carrier


readlineC :: H.InputT (Effly m) a -> ReadlineC m a
readlineC = coerce
 
instance
  ( Effs '[Embed IO, Mask, Bracket] m,
    Threads ReadlineT (Prims m)
  ) =>
  Carrier (ReadlineC m) where
  ...
  reformulate = 
    addDeriv (\case
        GetInputLine p -> liftBase $ readlineC $ H.getInputLine p
        ...
    ) $ ...

If you want to replace the Mask and Bracket membership constraints with MonadMask (which, upon further reflection, you probably should, as interpreting Mask and Bracket will impose primitive effects), then you need to replace uses of Effly above with EfflyIO:

readlineC :: H.InputT (EfflyIO m) a -> ReadlineC m a
readlineC = coerce
 
instance
  ( Eff (Embed IO) m,
    MonadMask m,
    Threads ReadlineT (Prims m)
  ) =>
  Carrier (ReadlineC m) where
  ...
  reformulate = 
    addDeriv (\case
        GetInputLine p -> liftBase $ readlineC $ H.getInputLine p
        ...
    ) $ ...

This also means you can use the new threadBaseControlViaUnlift in order to define a ThreadsEff (BaseControl b) ReadlineT instance.

Regarding extra constraints on interpreters:

  • That makes sense
  • I ran into an issue that could potentially benefit from a similar treatment too: Optional's state needing to be functorial.
    • It's possible that it isn't required in enough cases that you actually loose flexibility if you add a functor constraint to optionally but I was able to compile and run the small echo-repl example program in my package. When trying to actually call it from a bigger project I got an error saying that my functor for Optional (WithOrHandleInterrupt) was missing an instance for Functor.
    • I was able to isolate the issue to the functor instance being required when there is a threaders constraint. This commit introduces the issue in a minute example repl. The parent of the commit succeeds, but the commit fails with
      examples/Echo.hs:20:43: error:
          • No instance for (Functor
                               Control.Effect.Readline.Internal.WithOrHandleInterrupt)
              arising from a use of ‘repl’
          • In the second argument of ‘runReadline’, namely ‘repl’
            In the second argument of ‘($)’, namely
              ‘runReadline defaultSettings repl’
            In the expression: runM $ runReadline defaultSettings repl
         |
      20 | main = runM $ runReadline defaultSettings repl
         |                                           ^^^^
      

Regarding EfflyIO/Effly/coerce as a means of turning Eff (Embed IO) m into a MonadIO constraint:

  • That makes sense, and the boilerplate isn't that bad / is even better given its possible to coerce through InputT
  • I wonder if the precise circumstance requiring EfflyIO might be common enough to eventually have EfflyIO directly in in-other-words

Let me also give you a bit of a general review of in-other-words, I didn't give too much of my overall thoughts in my original comment:

  • Overall I found the library fairly easy to comprehend. Admittedly I am fairly experienced both with polysemy and more traditional MTL-style typeclasses + MonadBaseControl/MonadUnliftIO etc. so maybe this doesn't prove very much. Also huge props too your documentation page on advanced usage. It makes the advanced features of this library so much easier to comprehend than even interpreting fairly simple higher order effects using polysemy
  • I really appreciate still having a way of interpreting effects using a simple pattern matching style ala polysemy. I never wanted to try fused-effects because of lack of this
  • I also am fairly excited to see that this library is fairly "batteries included", including largish amounts of actions for Aynsc + LogicT style stuff in particular. I guess this is only possible because those effects are ill defined in polysemy/fused-effects but here you can get around that by preventing effects from being interpreted with one another
  • I was able to fairly painlessly port one of my small projects to in-other-words from polysemy, I'm guessing that threading constraints I'm guessing could get fairly annoying on a larger project though; I haven't tried using split interpretation yet to solve this issue because it hasn't gotten too annoying yet. I saw that you said you had tried an approach for "abstract interpreters" that would solve this, I'm a little bit curious how this might work

Closing as I don't have anything else to comment related to this, but open to further discussion