polysemy-research / polysemy-zoo

:monkey::panda_face: Experimental, user-contributed effects and interpreters for polysemy
BSD 3-Clause "New" or "Revised" License
70 stars 20 forks source link

Canonical effect #8

Closed adamConnerSax closed 5 years ago

adamConnerSax commented 5 years ago

Here's CanonicalEffect a little fleshed out. Didn't need the fundep. I did a few of them to see how they were to implement. I still don't love the class version but it does make things simpler at the user level. If this is how you want to move forward, I'll do it this way in RandomFu in that PR (after this one is merged, I guess?).

adamConnerSax commented 5 years ago

Yep! Will do.

adamConnerSax commented 5 years ago

I ended up not liking the class. Using it does get you the overloaded name but at the cost of requiring type-applications for both the MTL monad and the effect at every use site. So I think a user would write the monomorphic absorber each time anyway. And once they are doing that we can improve inference by writing absorbers that are at least polymorphic in the type of environment, log, state or error. So I switched to that. And I added tests of each. They are kind of boring but they do show that you can access the mtl-style function and the polysemy functions in the same do-block. If you approve of this basic design, I would be happy to write one more example demonstrating that the polysemy monad doing the absorbing can have many effects in it. Which might be useful since these examples are all single-effect. If you get more mtl-interop questions, it might be worth adding a short piece of documentation about the approaches that people might find useful (re-write in polysemy, run polysemy on top of mtl, absorb, ??).

adamConnerSax commented 5 years ago

Also, I'd be happy to add docs to each absorb function now if you think the signatures are not enough. And I'm not sure the name of it all makes as much sense without the Class.

isovector commented 5 years ago

This is brilliant. I want to investigate using type families to deconstruct arbitrary constraints --- in an attempt to automatically absorb several effects at once. Do you think we could do something like this:

type family Absorbing (r :: [(* -> *) -> * -> *]) (t :: *) :: Constraint where
  Absorbing (c => t) = (Absorb r c, Absorbing r t)
  Absorbing t = (() :: Constraint)

type family Absorb r c :: Constraint where
  Absorb (c1, c2, ... c8) => MembersForEachCanonical r '[c1, c2, ... c8]
  Absorb (c1, c2, ... c7) => MembersForEachCanonical r '[c1, c2, ... c7]
  -- etc

and where MembersForEachCanonical is the CanonicalEffect stuff. What do you think?

adamConnerSax commented 5 years ago

I like that idea! That would start to be killer-app-ish since then you could just wholesale use Polysemy against any mtl-constraint coded stack.

I'd started to think along those lines as well but not gotten as far along. And I don't quite understand what you're suggesting but that'l pass, I imagine. I'll see if I can get something like that working.

I do worry that the inference will get complex in ways that might make it hard to use, though maybe that could be confined to writing one tricky "run" function which, to be fair, is always where the rubber hits the road anyway. Can't do much more today, but I'll get back to it tomorrow or Tuesday.

adamConnerSax commented 5 years ago

Still don't quite get what you are thinking but I do think I have a variation on what I've already done which then uses deriving via to make the boilerplate on multiple-constraint versions pretty manageable. More later...

isovector commented 5 years ago

Alas, doesn't appear that it's possible to tyfam match on the left side of a => arrow.

I'm concerned about a deriving via --- it sounds like it's going to require O(2^(n+1)) definitions --- but will hold off worrying too much until I see the impl.

adamConnerSax commented 5 years ago

I don't think it will.
Deriving via lets you use the single effect wrappers to get the instance for a more complex wrapper. since they are all representationally equivalent. See the RWS example in the CanonicalEffect module. Note: I know this code is messy and uncommented. I'm headed out for the day but wanted you to have the chance to look at it. I'll clean up later if you think it's a good way to go.

isovector commented 5 years ago

The RWS example is really nice! It's cool that it can absorb three effects simultaneously!

That being said, notice that you can't use absorbRWS to absorb getEnvLength without also taking on the WS member constraints. Which means we're also going to also need absorbR. The argument generalizes for both W and S, as well as the combinations RW, RS, and WS.

As such, this approach requires a powerset (2^n) of absorb functions for the selection over n MTL effects. Add on the type definitions, and O(n) deriving vias for each type, and you've found yourself with a lot of definitions!

I think what we want instead is some sort of generic definition that is capable of farming itself out to the individual absorb calls. This is the gist of what I was trying to suggest above. Assume we have a typeclass that provides absorb for a single mtl effect, then:

absorbMany 
    :: (Absorbing c ~ 'Absorbed newMembers remnantConstraints)
    => Members newMembers r
    => remnantConstraints
    -> (c => result)
    -> result

data Absorbed = Absorbed [(* -> *) -> * -> *] Constraint

type family Absorbing (c :: Constraint) :: Absorbed where
  -- do this less stupidly, but serves to illustrate
  Absorbing (MonadState s) = 'Absorbed '[State s] ()
  Absorbing (MonadState s, Show Int) = 'Absorbed '[State s] (Show Int)
  Absorbing (MonadState s, MonadReader i, Enum Bool) = 'Absorbed '[State s, Reader i] (Enum Bool)

If we could write Absorbing, then this would let us do the thing in only O(n) boilerplate.

isovector commented 5 years ago

Absorbing can't be written without overlapping type families, and so it's probably impossible short of explicit compiler/plugin support. And it's not a feature I particularly want in the polysemy-plugin, as I'm trying to keep the amount of MAGIC in the library to an absolute minimum.

Any thoughts on this overwhelming tome I've written you over the last few posts? I"m not sure what is the best way to proceed.

adamConnerSax commented 5 years ago

Only short thoughts, though I appreciate the tome!

This feels like it already gets to a decent spot in the design space. It handles single effects pretty smoothly and you can handle a single given stack pretty easily as well, by simply writing the one newtype you need, and there derivingVia makes it very simple. And that covers a lot of use cases!

But I see what you are saying about how nice it would be if we could absorb any stack just given a list of constraints. But I can't see a why that doesn't involve orphan instances (use one newtype for everything), or, as you correctly point out, quadratic instances.

The one thought I had was something that, free-style, is either Sem r a or a thing which wraps such a thing. Maybe via type-family? But I can't quite figure out how it would work. I'm happy to keep thinking about it.

But what we have here is already pretty useful, I would think. You could release it like this, more or less--we need to think about names? Maybe add some more canonical effects?--and see how it gets used.

What do you think?

I feel like you were sort of against this all and now you've come around and want it to work for all the things...

isovector commented 5 years ago

Can we implement absorbRWS as absorbReader . absorbWriter . absorbState? If so I'm inclined to agree that we should roll with this. If we can do the above, let's just provide a single absorb for each of the effects in mtl plus a little guide (or stretch goal: TH) for lifting other mtl-style classes. Sound reasonable?

adamConnerSax commented 5 years ago

At this point we cannot write absorbRWS that way since each absorb function unwraps a specific newtype. I'm pondering a thing which would look something like

data WrappedSem (cs :: [(Type ->Type) -> Constraint]) r a where
  JustSem :: Sem r a -> WrappedSem cs r a
  WrappedSem :: (cs ~ (c ': ds), ConstrainAllM cs (WrappedSem cs r)) => WrappedSem ds r a -> WrappedSem cs r a

but while that's easily a functor, it might be too dependent-type-ish to be made Applicative or Monadic. Haven't tried hard enough yet. Might need some Nat style magic that I can't see yet. But it would be substantially more complex than what's there now, though it might solve the n^2 instances since it would just wrap the Sem with as many layers as it needs where each one has an instance for each MTL thing. But then that might lead us back to orphans! Oy.

I think we might need to live with an absorb function for each specific combination of MTL constraints. And while that's not great, I do think it's often all any user will need.

isovector commented 5 years ago

I don't think it's feasible to just do the powerset. Just to fill in all of the default mtl classes you're looking at 63 newtypes, 63 runAbsorbs and roughly 400 instances. And even after having done all that work, it still wouldn't solve the MonadRandom case!

So instead let's go back to the drawing board and figure out how to make these absorb functions compose with one another.

isovector commented 5 years ago

To express myself more succinctly:

The problem polysemy exists to solve is the the O(n^2) amount of boilerplate required to use mtl in a an extensible way. If doing that requires O(2^n) boilerplate, using polysemy is asymptotically worse than just not using it!

adamConnerSax commented 5 years ago

So, yes, I agree with all that. And I'm happy to keep hunting for a better solution.

We started all this to get rid of an orphan instance on RandomFu which I had placed there to allow a small sort of mtl-style/polysemy interoperation when the mtl dependency was only via constraint.

What we have so far (single absorbers for each effect, kit & example for combos) solves that problem in the sense that:

This solution has at least one drawback:

So we've drifted, at least from my perspective, from trying to solve an interop/migration problem--allowing people who want to use existing mtl-constraint-style stacks in polysemy code, to something more ambitious, trying to write an injective function from (some subset of) mtl-constrained actions to polysemy actions, and one that works without orphan instances or requiring combinatorically annoying numbers of types.

And that would be cool! But since it seems to me like a different goal than the one I started with, I'd like to make sure I understand it. Is what I said above about right?

without orphans and without a combinatoric explosion in types and functions required to support a larger set of possible members of c.

Is that about right?

Also, just so I understand, what use case(s) are you imagining? Are you thinking of someone slowly converting an existing mtl code-base to polysemy who keeps wanting to move the "absorption" point(s) deeper into the code? Or is this more philosophical?

isovector commented 5 years ago

That's a good summary of what's going on from my point of view. I don't see any distinction between this and the RandomFu example, but maybe I'm missing something here.

My understanding is that you have some functions (I can't remember if they're at the application or interpretation-level) you want to call that require a MonadRandom constraint. Rather than sendMing them from some existing MonadRandom instance, you'd like to put that MonadRandom instance on Sem and be able to call them directly. Since then it seems like I've been pushing you down the rabbit hole and it's not helping solve your immediate problem. Is this a relatively accurate description of your side of things?

isovector commented 5 years ago

Maybe we should schedule a call and hash this out in real time; might be an easier way to get on the same page!

adamConnerSax commented 5 years ago

Yep! Although I've already solved my immediate problem so that's fine. And the rabbit hole is kinda fun--currently back to fooling with reflection!--but yes, I just want to make sure that we agree on the goal, even if we have different motivations.

A call might be good! But I am about to get buried in relatives and whatnot (high-schooler about to graduate) so it's likely today or next week. Does later today work for you? I would like to fiddle with reflection a bit more to see if I can solve this to both our satisfaction. If that works, we can talk about how to deploy it, if not, we can try to figure out what to try next and/or what to do with what's already there. Does that make sense?

isovector commented 5 years ago

I'm free for the next couple hours; my id on google hangouts is sandy.g.maguire@gmail.com

adamConnerSax commented 5 years ago

Tried to message via hangout a couple of hours ago. Maybe I did it wrong? Anyway, I'm headed out soon and then buried in chaos until next week.

adamConnerSax commented 5 years ago

Short version: I've given up on reflection for now. Going at it directly that way doesn't solve the problem, or might but leave us with orphans again? I can't see a way to get away from orphans and n^2. But I'm open to suggestions!

isovector commented 5 years ago

Reflection is a good idea. How far did you get? I got up to here: https://github.com/ekmett/reflection/issues/43

adamConnerSax commented 5 years ago

Not that far! I did it via spun up instances on a newtype. So I would’ve hard orphan issues eventually. But I had fundamentally the same sigs and the same error. I’ll keep thinking about it. Maybe Ed will solve it!

isovector commented 5 years ago

I got it working!

{-# LANGUAGE ConstraintKinds       #-}
{-# LANGUAGE DerivingVia           #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables   #-}
{-# LANGUAGE UndecidableInstances  #-}
{-# OPTIONS_GHC -fplugin=Polysemy.Plugin  #-}

module Polysemy.MTL where

import qualified Control.Monad.Reader.Class as S
import qualified Control.Monad.State.Class as S
import           Data.Constraint
import           Data.Constraint.Unsafe
import           Data.Proxy
import           Data.Reflection
import           Data.Semigroup
import           Polysemy
import           Polysemy.Reader
import           Polysemy.State
import Unsafe.Coerce

newtype Lift1 (p :: (* -> *) -> Constraint) (m :: * -> *) (s) x = Lift1
  { lower1 :: m x
  } deriving (Functor, Applicative, Monad) via m

class ReifiableConstraint1 p where
  data Def1 (p :: (* -> *) -> Constraint) (m :: * -> *)
  reifiedIns1 :: Monad m => Reifies s (Def1 p m) :- p (Lift1 p m s)

-- > using (Monoid (+) 0) $ mappend mempty 12
-- > 12
using :: forall p m a. (Monad m, ReifiableConstraint1 p) => Def1 p m -> (p m => m a) -> m a
using d m =
  reify d $ \(_ :: Proxy s) -> m \\ trans (unsafeCoerceConstraint :: (p (Lift1 p m s) :- p m)) reifiedIns1

------------------------------------------------------------------------------
absorbReader :: Member (Reader i) r => (S.MonadReader i (Sem r) => Sem r a) -> Sem r a
absorbReader f = using (MonadReader ask local) f

instance ReifiableConstraint1 (S.MonadReader i) where
  data Def1 (S.MonadReader i) m = MonadReader
    { ask_ :: m i
    , local_ :: forall a. (i -> i) -> m a -> m a
    }
  reifiedIns1 = Sub Dict

instance ( Monad m
         , Reifies s' (Def1 (S.MonadReader i) m)
         ) => S.MonadReader i (Lift1 (S.MonadReader i) m s') where
  ask = Lift1 $ ask_ $ reflect $ Proxy @s'
  local f m = Lift1 $ local_ (reflect $ Proxy @s') f $ lower1 m

------------------------------------------------------------------------------
absorbState :: Member (State s) r => (S.MonadState s (Sem r) => Sem r a) -> Sem r a
absorbState f = using (MonadState get put) f

instance ReifiableConstraint1 (S.MonadState s) where
  data Def1 (S.MonadState s) m = MonadState { get_ :: m s, put_ :: s -> m () }
  reifiedIns1 = Sub Dict

instance ( Monad m
         , Reifies s' (Def1 (S.MonadState s) m)
         ) => S.MonadState s (Lift1 (S.MonadState s) m s') where
  get = Lift1 $ get_ $ reflect $ Proxy @s'
  put s = Lift1 $ put_ (reflect $ Proxy @s') s

foo :: (S.MonadReader Int m, S.MonadState String m) => m Int
foo = do
  r <- S.get
  S.put r
  S.ask

absorbRS
    :: forall r
     . ( Member (State String) r
       , Member (Reader Int) r
       )
    => Sem r Int
absorbRS = absorbState $ absorbReader foo
adamConnerSax commented 5 years ago

Nice! Should I try to understand it and generalize to type-lists if constraints? Might take me a bit...

adamConnerSax commented 5 years ago

For now, I will bring that module into the zoo, try to generalize and whatnot and then we'll see where we are? Or would you like to do that yourself? Once it's all nice, it should probably be in polysemy proper, right? It's incredibly useful.

isovector commented 5 years ago

I'm not sure generalizing it is necessary; writing a few absorbXs by hand seems like a reasonable tradeoff. What do you think?

isovector commented 5 years ago

You're more than welcome to take the ball on this one, but I don't mind running with it. It is your brainchild though!

adamConnerSax commented 5 years ago

Let me take a shot. I’d like to understand reflection better anyway. So for now, I’ll do Reader, Writer, State and Error? Anything else canonical? And then think about what to export to make rolling these for other effects, like RandomFu, easy to do in their own modules. You want to call it Polysemy.MTL? Polysemy.Absorb? Polysemy.CanonicalEffect? And which library do you want it in at this point?

isovector commented 5 years ago

Sounds great! I'm partial to Polysemy.MTL and would prefer to keep this out of the core lib---ideally one day we'll eat all of mtl's lunch, and then it'd be a weird dependency to have around. So I'm happy to keep this in the zoo, we can spin up the much discussed polysemy-contrib, or you can put it in its own package polysemy-mtl. Any preferences?

adamConnerSax commented 5 years ago
  1. You don't need deriving via since you can use GND. I like deriving via but it does put a lower bound on ghc version so I switched it. Is there some other difference that makes it worth keeping here?
  2. "using" is just absorb with the dictionary as an argument. So we can add one more class to hold the "canonical" sem dictionary. Then we can write a generalized absorb that uses type-applications to know what it's abosrbing. That seems useful since it removes a little boilerplate. But at the cost of requiring UndecidableSuperClasses and AllowAmbiguousTypes.
  3. Because "*" will eventually be deprecated (right?), I've switched 'em all to "Type".
  4. Also. I've renamed some things, which might be annoying. I can put them back. All the "Lift1", et. makes sense if you are coming from Constraints as a library but is sort of mysterious otherwise. Or we could document it and link back? But I think I prefer names that make more sense in context.
  5. I put the open type family for CanonicalEffect in here to make writing the generalized absorber possible. I don't think the constraint-list/Member-list type-families are worth it, though they would make stack-absorbers (see test/MTLSpec.hs) a bit simpler to express correctly. What do you think?
adamConnerSax commented 5 years ago

I'm happy to keep in the zoo for now.

adamConnerSax commented 5 years ago

I think I got them all. There was a bug in my implementation of pass (why are the writer versions so different?) but I think it's fixed. Your suggestion caught it by making sure it got used. And the rank-2 thing does indeed require some $ when you'd think . would work. I did what I could.

isovector commented 5 years ago

This is looking great! I'm happy to merge it whenever you are

isovector commented 5 years ago

I think the discrepencies in Writer are a bug on my part.

On Thu, May 30, 2019 at 12:10 AM Adam Conner-Sax notifications@github.com wrote:

I think I got them all. There was a bug in my implementation of pass (why are the writer versions so different?) but I think it's fixed. Your suggestion caught it by making sure it got used. And the rank-2 thing does indeed require some $ when you'd think . would work. I did what I could.

— You are receiving this because you commented. Reply to this email directly, view it on GitHub https://github.com/isovector/polysemy-zoo/pull/8?email_source=notifications&email_token=AACLAFYFPGMITCKBJLL4YYTPX5HTBA5CNFSM4HPVKOD2YY3PNVWWK3TUL52HS4DFVREXG43VMVBW63LNMVXHJKTDN5WW2ZLOORPWSZGODWRJQ5I#issuecomment-497195125, or mute the thread https://github.com/notifications/unsubscribe-auth/AACLAFZN2IMOZFJG5LWS263PX5HTBANCNFSM4HPVKODQ .

adamConnerSax commented 5 years ago

Had one last unnecessary comment and a typo. Those are fixed. If you're happy, merge away!

adamConnerSax commented 5 years ago

One thought, not for now: you could put the generalized stuff in polysemy itself--something like "Polysemy.Absorb" or "Polysemy.AbsorbConstraint"--without any MTL dependencies and likely without the CanonicalEffect type-family. Then just put the specific MTL absorbers in the zoo. Now you don't have an MTL dependency in polysemy proper but you do have the tools for handling interoperation there.
Probably worth leaving it here for a while, though, and seeing if there are issues and how it gets used.

adamConnerSax commented 5 years ago

Ah. A couple of late night mistakes are left. I forgot to export the member functions of the classes. And we should probable re-export Reifies to save anyone using all this from needing to import, and explicitly depend on reflection. How shall I proceed? I can fix in another PR? Or we can revert this one and then do it again?