snowleopard / selective

Selective Applicative Functors: Declare Your Effects Statically, Select Which to Execute Dynamically
MIT License
202 stars 21 forks source link

Composition w/ Selective #12

Open m00ngoose opened 5 years ago

m00ngoose commented 5 years ago

I was wondering if it mightn't be instructive to somewhere discuss what happens when you try to compose with Selective functors.

It seemed to me that you can only ever recover the selectivity of the inner functor, ie.

Applicative f, Selective g => Selective (Compose f g) where
    select (Compose fg) (Compose fg') = Compose $ liftA2 select fg fg'

The outer functor f is executed unconditionally, but selective behaviour of the inner functor g is preserved.

I believe (?) that eg. Selective f, Selective g doesn't permit conditional execution of f in Selective (Compose f g), likewise Selective f, Applicative g.

Does this perhaps help illustrate the way in which the potential effects are statically constrained - in particular the selective execution can't depend on the results of other arbitrary functors which with they are composed?

Also, is there any scope for exploring a stronger notion of "compositional selectivity"? Where we would be allowed to say if f, g do not execute the unchosen branch, then their composition won't do either?

snowleopard commented 5 years ago

@awhtayler Yes, that's an interesting question which I've been thinking about for a while. We do have the instance you mention:

https://github.com/snowleopard/selective/blob/edd7dfc21dbc0c89cf08be93fb4e54ffb7ff8400/src/Control/Selective.hs#L392-L393

In a way, you can say that this composition uses selectA on the outer layer. It might also be possible to define a reasonable instance with constraint Monad f on the outer layer, corresponding to using selectM.

Curiously, Alternative has the flipped order of constraints:

instance (Alternative f, Applicative g) => Alternative (Compose f g) where

Does this perhaps help illustrate the way in which the potential effects are statically constrained - in particular the selective execution can't depend on the results of other arbitrary functors which with they are composed?

Maybe, but I'd like to make this intuition a bit more precise. Could you elaborate a bit further?

Also, is there any scope for exploring a stronger notion of "compositional selectivity"? Where we would be allowed to say if f, g do not execute the unchosen branch, then their composition won't do either?

As we discuss in the paper, there are some alternative definitions of selective functors, which include methods like branch, bindS or biselect, but I don't think that any of these alternatives makes selective functors "more composable". Perhaps, selective functors are just too close to monads, which are also not composable? I don't have good answers to these questions, but they are very interesting! Any insights would be very helpful!

snowleopard commented 5 years ago

Here is an example showing why composing selective functors is tricky.

Consider Compose Maybe IO. The only sensible implementation is:

select :: Maybe (IO (Either a b)) -> Maybe (IO (a -> b)) -> Maybe (IO b)
select Nothing  _        = Nothing
select (Just x) (Just y) = Just (select x y)
select (Just x) Nothing  = Nothing -- Can't use Just: we don't have the function a -> b!

In other words, we have to be Applicative on the outside functor Maybe, because there is no way to peek inside IO, which forces us to statically choose between Just, which doesn't work since we have no function a -> b, and Nothing which corresponds to the behaviour of selectA.

turion commented 3 years ago

If your inner functor is also Traversable, you can peek inside it to some extent:

instance (Applicative g, Traversable g, Selective g) => Selective (Compose Maybe g) where
  select (Compose Nothing) (Compose Nothing) = Compose Nothing
  select (Compose Nothing) (Compose (Just g)) = Compose Nothing
  select (Compose (Just g)) (Compose Nothing) = Compose $ either (const Nothing) Just $ sequenceA g
  select (Compose (Just g)) (Compose (Just g')) = Compose $ Just $ select g g'

The key is that we can sequenceA the g :: g (Either a b) to find out whether it consists of only Right b's. In that case, we don't need the second argument.

I didn't check the laws though.

There is a generalisation of this idea:

instance (Traversable g, Applicative g, Selective f) => Selective (Compose f g) where
    select (Compose eab) (Compose fab) = Compose $ select (sequenceA <$> eab) (sequenceA <$> fab)

The first sequenceA says "Check whether all Eithers in eab are Rights, otherwise short-circuit on the first Left a you encounter" and the second sequenceA says "Broadcast the a to all functions in fab".

Again I didn't check the laws, but we could start that with some property tests, and then look for a proof.

turion commented 3 years ago

A lot of functors are traversable. Most from base are. Also WriterT and ListT.

Any functor of the sort r -> a is not traversable unless we know that r is "finite" in some sense. So maybe there is some leeway for Enumerable here. Or else one could write instances (Bounded r, Enum r, Traversable m) => Traversable (ReaderT r m), and the same for StateT and AccumT. Whether this is efficient is a different question, since it needs to check all possible environments to find out whether maybe the last one does have a Left a.

turion commented 3 years ago

Let's look at some laws.

Identity

x <*? pure id
-- definition of my instance and `Applicative Compose`
= Compose $ select (sequenceA <$> getCompose x) (sequenceA <$> pure (pure id))
-- `Applicative` law
= Compose $ select (sequenceA <$> getCompose x) (pure sequenceA <*> pure (pure id))
-- `Applicative` law
= Compose $ select (sequenceA <$> getCompose x) (pure (sequenceA id))
-- `Functor` and `Traversable` law
= Compose $ select (sequenceA <$> getCompose x) (pure id)
-- `Selective` law
= Compose $ either id id <$> (sequenceA <$> getCompose x)
-- Definition of `Compose`
= either id id <$> x

Distributivity

pure x <*? (y *> z)
-- definition of instance and `Applicative Compose`
= Compose $ select (sequenceA <$> pure (pure x)) (getCompose (y *> z))
-- `Applicative` law
= Compose $ select (pure sequenceA <*> pure (pure x)) (getCompose (y *> z))
-- `Applicative` law
= Compose $ select (pure (sequenceA (pure x))) (getCompose (y *> z))
-- `Compose` & `Applicative` lemma
= Compose $ select (pure (sequenceA (pure x))) (getCompose y *> getCompose z)
-- `Selective` law
= Compose $ select (pure (sequenceA (pure x))) (getCompose y) *> (pure (sequenceA (pure x))) (getCompose z)
-- Previous steps backwards
= (pure x <*? y) *> (pure x <*? z)

Associativity

That sounds hard.

turion commented 3 years ago

Note

By the way, the second sequenceA isn't necessary:

instance (Traversable g, Applicative g, Selective f) => Selective (Compose f g) where
    select (Compose eab) (Compose fab) = Compose $ select (sequenceA <$> eab) (strength <$> fab)

strength :: Functor g => g (a -> b) -> a -> g b
strength g a = fmap ($ a) g

This is because in Haskell, every functor is strong. But to get something of type f (Either ...) from f (g (Either a b)) we probably need sequenceA.

turion commented 3 years ago

Associativity

To prove:

x <*? (y <*? z) = (f <$> x) <*? (g <$> y) <*? (h <$> z)
  where
    f :: Either a b -> Either a (Either e b)
    f x = Right <$> x
    g :: Either c (a -> b) -> a -> Either (c, a) b
    g y = \a -> bimap (,a) ($a) y
    h :: (c -> a -> b) -> (c, a) -> b
    h z = uncurry z
((f <$> x) <*? (g <$> y)) <*? (h <$> z)
-- Definition
= Compose $ (sequenceA <$> getCompose (f <$> x)) <*? (sequenceA <$> getCompose (g <$> y)) <*? (sequenceA <$> getCompose (h <$> z))
-- Definition of `<$>` in `Compose`
= Compose $ (sequenceA <$> (fmap f <$> getCompose x)) <*? (sequenceA <$> (fmap g <$> getCompose y)) <*? (sequenceA <$> (fmap h <$> getCompose z))
-- `<$>` law
= Compose $ (sequenceA . fmap f <$> getCompose x) <*? (sequenceA . fmap g <$> getCompose y) <*? (sequenceA . fmap h <$> getCompose z)
-- Naturality of `Traversable` (https://hackage.haskell.org/package/base-4.12.0.0/docs/Data-Traversable.html#t:Traversable)
-- Since `f`, `g` and `h` are applicative transformations
= Compose $ (f . sequenceA <$> getCompose x) <*? (g . sequenceA <$> getCompose y) <*? (h . sequenceA <$> getCompose z)
-- `<$>` law
= Compose $ (f <$> sequenceA <$> getCompose x) <*? (g <$> sequenceA <$> getCompose y) <*? (h <$> sequenceA <$> getCompose z)
-- Associativity of underlying `Selective`
= Compose $ (sequenceA <$> getCompose x) <*? ((sequenceA <$> getCompose y) <*? (sequenceA <$> getCompose z))
-- Definition of instance
= x <*? (y <*? z)

Bottom line

So I guess we have a Selective instance even when the outer functor of the composition is Selective! The only downside is that the inner functor must be Traversable, and in the worst case the whole structure must be traversed.

By the way, the Applicative instance for the inner functor is not used here, but it is still needed for instance Applicative (Compose f g) which is a superclass of instance Selective (Compose f g). We could of course recover <*> via apS, so g only needs to have a pure function, and not the whole Applicative structure. But I'm not sure that's worth the effort.

Lemmata: f, g and h are applicative transformations

turion commented 3 years ago

Note

By the way, the second sequenceA isn't necessary:

instance (Traversable g, Applicative g, Selective f) => Selective (Compose f g) where
    select (Compose eab) (Compose fab) = Compose $ select (sequenceA <$> eab) (strength <$> fab)

strength :: Functor g => g (a -> b) -> a -> g b
strength g a = fmap ($ a) g

The two definitions are equivalent since for any Traversable it is required that:

fmap f = runIdentity . sequenceA . fmap (Identity . f)

And thus strength is the same as sequenceA:

strength g a
= fmap ($ a) g
= (runIdentity . sequenceA . fmap (Identity . ($ a))) g
-- Naturality of `sequenceA`.
-- Now this is just a silly way of currying:
= (($ a) . sequenceA) g
-- Let's eta-expand to see this
= (\g' -> ($ a) $ sequenceA g') g
= (\g' -> sequenceA g' a) g
= sequenceA g a

So for proofs and reasoning we may still assume that the instance is defined symmetrically with sequenceA for both parts, but in practice strength might be faster because it only needs Functor.

snowleopard commented 3 years ago

@turion Cool, thanks for working out all the proofs! I did know that one can get the composition to type check with Traversable but I never looked into proving the laws.

One problem with using this definition is that it looks somewhat arbitrary (just like the one used in the library at the moment). Let's look at the two instances:

Why would one pick one over the other? Surely, neither of them is more general.

Intuitively, we want the composition of two selective functors to "respect" their individual selectivity, but neither of these instances can do that since they use only one select in their definitions!

I suspect we are really looking for instance (Selective f, Selective g, ExtraF f, ExtraG g) => Selective (Compose f g) for some as yet unknown values of ExtraF and ExtraG. Do you agree?

turion commented 3 years ago

Why would one pick one over the other? Surely, neither of them is more general.

Yes, that's true. There can be situations where only one applies, or maybe even both. For the case that both apply, we'd need two different newtypes. It would be interesting to see whether the two variants agree in such a case, or what extra compatibility between select and sequenceA and <*> must hold for that.

Intuitively, we want the composition of two selective functors to "respect" their individual selectivity, but neither of these instances can do that since they use only one select in their definitions!

Yes, that's strange. I see this as both a strength and a weakness. The strength in this is that we can sometimes combine a Selective with another functor that is not a Selective (in one case not even an Applicative). So we have more choice. The weakness is that with this path forward, selective functors don't form a category.

I suspect we are really looking for instance (Selective f, Selective g, ExtraF f, ExtraG g) => Selective (Compose f g) for some as yet unknown values of ExtraF and ExtraG. Do you agree?

I agree that this would be the optimum. But I'm not sure it's achievable. In some sense you already have this for the first definition, since Selective and a function pure :: a -> f a give you an Applicative via apS, so your remaining constraint ExtraF is having a pure function.

For the second definition, it is the other way around. You probably already know that Applicative and Traversable give Selective:


newtype TraverseSelective f a = TraverseSelective { getTraverseSelective :: f a }
    deriving (Functor, Applicative)

instance (Applicative f, Traversable f) => Selective (TraverseSelective f) where
    select eab fab = TraverseSelective $ either (strength $ getTraverseSelective fab) id $ sequenceA $ getTraverseSelective eab

In fact, the Selective instance for [] (and possibly others) is isomorphic to this one. So in your words, we could also say that ExtraF is no constraints, and ExtraG amounts to demanding that the Selective g comes from a Traversable.

But there is some inherent choice in this. I'm not sure there is a way to have a more general formulation that encompasses both.

In fact, I'd intuitively think that this can't be. Selective means that you have to make one binary choice at some point, either execute the second thing or don't. I don't understand how this choice can be done in two contexts. If one of the contexts reaches that decision, it doesn't make much sense for the other one to make the decision again. Instead it seems natural to delegate the decision to one of the contexts, either inner or outer, and let the other context facilitate it. If we decide in the outer context, the inner one has to aggregate the decision over all possible positions, hence sequenceA. If we decide in the inner context, the outer one has to make sure we can combine values in it, hence Applicative.

snowleopard commented 3 years ago

For the second definition, it is the other way around. You probably already know that Applicative and Traversable give Selective

Actually, I didn't know about it, thanks for sharing! Now the two Selective (Compose f g) instances start to look pretty natural. The "missing" selective functors are substituted by selectA and selectT, which are opposites in the same sense as Over and Under are opposites:

selectA :: Applicative f => f (Either a b) -> f (a -> b) -> f b
selectA x y = (\e f -> either f id e) <$> x <*> y

selectT :: (Applicative f, Traversable f) => f (Either a b) -> f (a -> b) -> f b
selectT x y = case sequenceA x of
    Left  a  -> ($a) <$> y
    Right fb -> fb

λ> selectA (Const "x") (Const "y")
Const "xy"
λ> selectT (Const "x") (Const "y")
Const "x"

In fact, I'd intuitively think that this can't be. Selective means that you have to make one binary choice at some point, either execute the second thing or don't. I don't understand how this choice can be done in two contexts. If one of the contexts reaches that decision, it doesn't make much sense for the other one to make the decision again. Instead it seems natural to delegate the decision to one of the contexts, either inner or outer, and let the other context facilitate it. If we decide in the outer context, the inner one has to aggregate the decision over all possible positions, hence sequenceA. If we decide in the inner context, the outer one has to make sure we can combine values in it, hence Applicative.

Yes, this makes a lot of sense.

turion commented 3 years ago

Comment

One would usually call functorial strength this function:

strength :: Functor g => (a, g b) -> g (a, b)
strength (a, gb) = (a, ) <$> gb

With currying and function application we arrive at the other function strength :: Functor g => g (a -> b) -> a -> g b. I think they are essentially equivalent.

But there is a co-concept to that, by replacing products with sums and reversing the direction of the arrows:

class Functor f => Costrong f where
    costrength :: f (Either a b) -> Either a (f b)

This is not automatically satisfied for Haskell functors. But it exists for Traversable functors. (It might be less restrictive than Traversable, but I can't think of a functor that has Costrong that is not Traversable.)

The punch line is that strength + costrength both define a Selective instance, i.e. we have Functor f, Costrong f => Selective f, and that both Functor and Costrong compose.

Relation to your observation

So since selectA and selectT are clearly different, there can be different Selectives for the same Applicative. Both of these canonical ones compose with themselves, because Applicative and Traversable/Costrong all compose with themselves. More even, each of selectA and selectT compose with any select.

Composition of extra structures

But it's unclear how, or whether two general select compose.

Applicatives compose in a canonical way. By this I mean that for two given functors f and g with the canonical fmap for Compose f g, we construct the well-known (Applicative f, Applicative g) => Applicative (Compose f g) instance, and both gLift = Compose . pure and fLift = Compose . fmap pure are applicative morphisms from g and f to Compose f g.

Depending on what the functors are, there may be other ways to give Compose f g an Applicative, together with these morphisms, but the existence of this canonical thing that always works is already awesome. And it uses both applicative structures, as it must if we want to have applicative morphisms fLift and gLift.

Monads only compose when given a distributive law g (f a) -> f (g a), and I think even for two given Applicatives on f and g, for two monads on f and g there may be none, one, or many distributive laws. My vague impression is that given a distributive law, gLift and fLift are again monad morphisms.

I'm wondering how the choice of distributive law can change the selectM.

Selective morphisms

Definition: Let f and g be Selectives. A natural transformation nat :: f a -> g a is a "selective morphism" when select (nat eab) (nat fab) = nat $ select eab fab.

Question: Is there a Selective structure on Compose f g such that gLift and fLift are selective morphisms?

If yes, then I think this is "The Right" composed structure. It necessarily has to incorporate both selects somehow. There is no surprise when passing from one constituent f or g to Compose f g.

But right now my impression is that there is no such structure canonically for all selective functors. Our two cases seem not to give rise to selective morphisms because they don't use both selective structures. (And my variant even needs an extra typeclass.)

Another line of research might be looking for a "distributive law", maybe something like f (g (Either a b)) -> f (Either a (g b)).

snowleopard commented 3 years ago

Aha, Costrong seems like a fitting abstraction! What are the laws?

Note that there seem to be yet another implementation of select, based on a flipped version of costrength:

class Costrong2 f where
    costrength2 :: f (Either a b) -> Either (f a) b

selectC2 :: (Applicative f, Costrong2 f) => f (Either a b) -> f (a -> b) -> f b
selectC2 x y = case costrength2 x of
    Left fa -> fa <**> y
    Right b -> pure b

Not sure it makes sense but symmetry would suggest that it should.

I like how you frame the composition problem in terms of "selective morphisms"!

turion commented 3 years ago

Good point about your Costrong2. I agree, this will probably give another lawful Selective.

It's probably clear, but let me just note that every functor that has Costrong has also Costrong2, and vice versa.

For functorial strength I believe no other laws than naturality are required, so translated to Costrong it might be something like either f g <$> fab = either (fmap f) g $ costrength fab.

In the proof for Selective I also used that sequenceA (which specialises to costrength) is a morphism of applicatives. But I only used it in 3 special cases, so it might well be that they all hold for costrength and/or costrength2.

snowleopard commented 3 years ago

It's probably clear, but let me just note that every functor that has Costrong has also Costrong2, and vice versa.

Sure, I can see that.

Good point about your Costrong2. I agree, this will probably give another lawful Selective.

On the one hand, this makes the picture less clear. On the other hand, it's probably not surprising that one can come up with a lot of different ways to construct selective functors. There are many functors and many ways to make decisions based on different flavours of "inspectability", including oddities like "if the third element of the traversable functor is Left do this, otherwise do that".

turion commented 3 years ago

Yes, there is suddenly a big design space. The difference between Costrong and Costrong2 is not a difference between which functors to use, but how to use them. Costrong2 favours the happy path, i.e. it'll be fast if costrength2 returns a Right b. Costrong on the other hand short-circuits on a Left. Also, the selectC2 implementation from Costrong2 actually uses the Applicative in that it builds up a pure structure. The variant from Costrong doesn't do that, it takes either the structure from the first or the second argument.

So, yes, I agree, there doesn't seem to be one clear way to compose them, but lots of clever and also silly ways. The right question still is "what's the most general extra structure to give a Selective structure to the composition?", but I can't see yet how all these examples are special cases of one kind of structure.