While thinking about how to generalize monads, I came up with the following property of a functor F:
inject :: (a -> F b) -> F(a -> b)
To improve terminology a little bit, I propose to call these functors "rigid" instead of "bindable". The motivation for saying "rigid" will be explained below.
A functor f
is called rigid if it has the inject
method as shown. Note that every functor has the eject
method.
class (Functor f) => Rigid f where
inject :: (a -> f b) -> f(a -> b)
eject :: f(a -> b) -> a -> f b
eject fab x = fmap (\ab -> ab x) fab
The law of "nondegeneracy" must hold:
eject . inject = id
A rigid functor is always pointed:
instance (Rigid f) => Pointed f where
point :: t -> f t
point x = fmap (const x) (inject id)
If a rigid functor is applicative then it is automatically monadic:
instance (Rigid f, Applicative f) => Monad f where
bind :: f a -> (a -> f b) -> f b
bind fa afb = (inject afb) <*> fa
The property of being rigid is not comparable (neither weaker nor stronger) than the property of being monadic: If a functor is rigid, it does not seem to follow that it is automatically monadic (although I don't know specific counterexamples for this case). If a functor is monadic, it does not follow that it is rigid (there are counterexamples).
Basic counterexamples of monadic functors that are not rigid are Maybe
and List
. These are functors that have more than one constructor: such functors cannot be rigid.
The problem with implementing inject
for Maybe
is that inject
must transform a function of type a -> Maybe b
into Maybe(a -> b)
while Maybe
has two constructors. A function of type a -> Maybe b
could return different constructors for different values of a
. However, we are supposed to construct a value of type Maybe(a -> b)
. If for some a
the given function produces Nothing
, we don't have a b
so we can't produce a total function a->b
. Thus we cannot return Just(a->b)
; we are forced to return Nothing
as long as the given function produces Nothing
even for one value of a
. But we cannot check that a given function of type a -> Maybe b
produces Just(...)
for all values of a
. Therefore we are forced to return Nothing
in all cases. This will not satisfy the law of nondegeneracy.
So, we can implement inject
if f t
is a container of "fixed shape" (having only one constructor). Hence the name "rigid".
Another explanation as to why rigidity is more restrictive than monadicity is to consider the naturally defined expression
(inject id) :: f(f a -> a)
where id :: f a -> f a
. This shows that we can have an f-algebra f a -> a
for any type a
, as long as it is wrapped inside f
. It is not true that any monad has an algebra; for example, the various "future" monads as well as the IO
monad describe computations of type f a
that do not allow us to extract values of type a
- we shouldn't be able to have a method of type f a -> a
even if wrapped inside an f
-container. This shows that the "future" monads and the IO
monad are not rigid.
A property that is strictly stronger than rigidity is distributivity from one of E. Kmett's packages. A functor f
is distributive if we can interchange the order as in p (f t) -> f (p t)
for any functor p
. Rigidity is the same as being able to interchange the order only with respect to the "reader" functor r t = a -> t
. So, all distributive functors are rigid.
All distributive functors are necessarily representable, which means they are equivalent to the "reader" functor c -> t
with some fixed type c
. However, not all rigid functors are representable. An example is the functor g
defined by
type g t = (t -> r) -> t
The functor g
are not equivalent to c -> t
with a fixed type c
.
Further examples of rigid functors that are not representable (i.e. not "distributive") are functors of the form a t -> f t
where a
is any contrafunctor and f
is a rigid functor. Also, the Cartesian product and the composition of two rigid functors is again rigid. In this way, we can produce many examples of rigid functors within the exponential-polynomial class of functors.
My answer to What is the general case of QuickCheck's promote function? also lists the constructions of rigid functors:
f = Identity
f
and g
are both rigid then the functor product h t = (f t, g t)
is also rigidf
and g
are both rigid then the composition h t = f (g t)
is also rigidf
is rigid and g
is any contravariant functor then the functor h t = g t -> f t
is rigidOne other property of rigid functors is that the type r ()
is equivalent to ()
, i.e. there is only one distinct value of the type r ()
. This value is point ()
, where point
is defined above for any rigid functor r
. (I have a proof but I will not write it here, because I could not find an easy one-line proof.) A consequence is that a rigid functor must have only one constructor. This immediately shows that Maybe
, Either
, List
etc. cannot be rigid.
If f
is a monad that has a monad transformer of the "composed-outside" kind, t m a = f (m a)
, then f
is a rigid functor.
The "rigid monads" are possibly a subset of rigid functors because construction 4 only yields a rigid monad if f
is also a rigid monad rather than an arbitrary rigid functor (but the contravariant functor g
can still be arbitrary). However, I do not have any examples of a rigid functor that is not also a monad.
The simplest example of a rigid monad is type r a = (a -> p) -> a
, the "search monad". (Here p
is a fixed type.)
To prove that a monad f
with the "composed-outside" transformer t m a = f (m a)
also has an inject
method, we consider the transformer t m a
with the foreign monad m
chosen as the reader monad, m a = r -> a
. Then the function inject
with the correct type signature is defined as
inject = join @t . return @r . (fmap @m (fmap @f return @m))
with appropriate choices of type parameters.
The non-degeneracy law follows from the monadic naturality of t
: the monadic morphism m -> Identity
(substituting a value of type r
into the reader) is lifted to the monadic morphism t m a -> t Id a
. I omit the details of this proof.
Finally, I found two use cases for rigid functors.
The first use case was the original motivation for considering rigid functors: we would like to return several monadic results at once. If m
is a monad and we want to have fbind
as shown in the question, we need f
to be rigid. Then we can implement fbind
as
fbind :: m a -> (a -> f (m b)) -> f (m b)
fbind ma afmb = fmap (bind ma) (inject afmb)
We can use fbind
to have monadic operations that return more than one monadic result (or, more generally, a rigid functor-ful of monadic results), for any monad m
.
The second use case grows out of the following consideration. Suppose we have a program p :: a
that internally uses a function f :: b -> c
. Now, we notice that the function f
is very slow, and we would like to refactor the program by replacing f
with a monadic "future" or "task", or generally with a Kleisli arrow f' :: b -> m c
for some monad m
. We, of course, expect that the program p
will become monadic as well: p' :: m a
. Our task is to refactor p
into p'
.
The refactoring proceeds in two steps: First, we refactor the program p
so that the function f
is explicitly an argument of p
. Assume that this has been done, so that now we have p = q f
where
q :: (b -> c) -> a
Second, we replace f
by f'
. We now assume that q
and f'
are given. We would like to construct the new program q'
of the type
q' :: (b -> m c) -> m a
so that p' = q' f'
. The question is whether we can define a general combinator that will refactor q
into q'
,
refactor :: ((b -> c) -> a) -> (b -> m c) -> m a
It turns out that refactor
can be constructed only if m
is a rigid functor. In trying to implement refactor
, we find essentially the same problem as when we tried to implement inject
for Maybe
: we are given a function f' :: b -> m c
that could return different monadic effects m c
for different b
, but we are required to construct m a
, which must represent the same monadic effect for all b
. This cannot work, for instance, if m
is a monad with more than one constructor.
If m
is rigid (and we do not need to require that m
be a monad), we can implement refactor
:
refactor bca bmc = fmap bca (inject bmc)
If m
is not rigid, we cannot refactor arbitrary programs. So far we have seen that the continuation monad is rigid, but the "future"-like monads and the IO
monad are not rigid. This again shows that rigidity is, in a sense, a stronger property than monadicity.
I have been doing some experiments lately to better understand Distributive
. Happily enough, my results appear closely related to your rigid functors, in a way that clarifies them both.
To begin with, here is one possible presentation of rigid functors. I have taken the liberty to bikeshed your names a bit, for reasons I'll soon get to:
flap :: Functor f => f (a -> b) -> a -> f b
flap u a = ($ a) <$> u
class Functor g => Rigid g where
fflip :: (a -> g b) -> g (a -> b)
fflip f = (. f) <$> extractors
extractors :: g (g a -> a)
extractors = fflip id
-- "Left inverse"/non-degeneracy law: flap . fflip = id
instance Rigid ((->) r) where
fflip = flip
Some remarks on my phrasing:
I have changed the names of inject
and eject
to fflip
and flap
, mainly because, to my eyes, flap
looks more like injecting, due to things like this:
sweep :: Functor f => f a -> b -> f (a, b)
sweep u b = flap ((,) <$> u) b
I took the flap
name from protolude. It is a play on flip
, which is fitting because it is one of two symmetrical ways of generalising it. (We can either pull the function outside of an arbitrary Functor
, as in flap
, or pull a Rigid
functor outside of a function, as in fflip
.)
I first realised the significance of extractors
while playing with Distributive
, but it hadn't occured to me that it might make sense as part of a different class. extractors
and fflip
are interdefinable, making it possible to write, for example, this rather neat instance for the search/selection monad:
newtype Sel r a = Sel { runSel :: (a -> r) -> a }
deriving (Functor, Applicative, Monad) via SelectT r Identity
instance Rigid (Sel r) where
-- Sel r (Sel r a -> a) ~ ((Sel r a -> a) -> r) -> Sel r a -> a
extractors = Sel $ \k m -> m `runSel` \a -> k (const a)
Every distributive functor is rigid:
fflipDistrib :: Distributive g => (a -> g b) -> g (a -> b)
fflipDistrib = distribute @_ @((->) _)
-- From this point on, I will pretend Rigid is a superclass of Distributive.
-- There would be some tough questions about interface ergonomics if we were
-- writing this into a library. We don't have to worry about that right now,
-- though.
From the other direction, we can write a function which imitates the signature of distribute
using Rigid
:
infuse :: (Rigid g, Functor f) => f (g a) -> g (f a)
infuse u = (<$> u) <$> extractors
infuse
, however, is not distribute
. As you note, there are rigid functors that are not distributive, such as Sel
. Therefore, we have to conclude that infuse
, in the general case, does not follow the distributive laws.
(An aside: that infuse
is not a lawful distribute
in the case of Sel
can be established by a cardinality argument. If infuse
followed the distributive laws, we would have infuse . infuse = id
for any two rigid functors. However, something like infuse @((->) Bool) @(Sel r)
leads to a result type with fewer inhabitants than the argument type; therefore, there is no way it can have a left inverse.)
At this point, it would be relevant to sharpen our picture of exactly what distinguishes Distributive
from Rigid
. Given that your rigid law is flap . fflip = id
, intuition suggests the other half of an isomorphism, fflip . flap = id
, might hold in the case of Distributive
. Checking that hypothesis requires a detour through Distributive
.
There is an alternative presentation of Distributive
(and Rigid
) in which distribute
(or fflip
) is factored through the function functor. More specifically, any functorial value of type g a
can be converted into a CPS suspension that takes a forall x. g x -> x
extractor:
-- The existential wrapper is needed to prevent undue specialisation by GHC.
-- With pen and paper, we can leave it implicit.
-- Note this isn't necessarily the best implementation available; see also
-- https://stackoverflow.com/q/56826733/2751851
data Ev g a where
Ev :: ((g x -> x) -> a) -> Ev g a
-- Existential aside, this is ultimately just a function type.
deriving instance Functor (Ev g)
-- Morally, evert = flip id
evert :: g a -> Ev g a
evert u = Ev $ \e -> e u
If g
is Rigid
, we can go in the other direction and recover the functorial value from the suspension:
-- Morally, revert = flip fmap extractors
revert :: Rigid g => Ev g a -> g a
revert (Ev s) = s <$> extractors
Ev g
itself is Distributive
, regardless of what g
is -- after all, it is just a function:
-- We need unsafeCoerce (yikes!) because GHC can't be persuaded that we aren't
-- doing anything untoward with the existential.
-- Note that flip = fflip @((->) _)
instance Rigid (Ev g) where
fflip = Ev . flip . fmap (\(Ev s) -> unsafeCoerce s)
-- Analogously, flap = distribute @((->) _)
instance Distributive (Ev g) where
distribute = Ev . flap . fmap (\(Ev s) -> unsafeCoerce s)
Further, fflip
and distribute
for arbitrary Rigid
/Distributive
functors can be routed through evert
and revert
:
-- fflip @(Ev g) ~ flip = distribute @((->) _) @((->) _)
fflipEv :: Rigid g => (a -> g b) -> g (a -> b)
fflipEv = revert . fflip . fmap evert
-- distribute @(Ev g) ~ flap = distribute @((->) _) _
distributeEv :: (Rigid g, Functor f) => f (g a) -> g (f a)
distributeEv = revert . distribute . fmap evert
revert
, in fact, would be enough for implementing Distributive
. In such terms, the distributive laws amount to requiring evert
and revert
being inverses:
revert . evert = id -- "home" roundtrip, right inverse law
evert . revert = id -- "away" roundtrip, left inverse law
The two roundtrips correspond, respectively, to the two non-free distributive laws:
fmap runIdentity . distribute = runIdentity -- identity
fmap getCompose . distribute = distribute . fmap distribute . getCompose -- composition
(The distribute . distribute = id
requirement stated in the Data.Distributive
docs ultimately amounts to those two laws, plus naturality.)
Earlier on, I speculated about an isomorphism involving fflip
:
flap . fflip = id -- "home" roundtrip, left inverse Rigid law
fflip . flap = id -- "away" roundtrip, would-be right inverse law
It can be verified directly that the rigid law, flap . fflip = id
, is equivalent to the other "home" roundtrip, revert . evert = id
. The other direction is trickier. The purported isomorphisms can be chained like this:
g (a -> b)
{fflip => <= flap} {evert => <= revert}
a -> g b Ev g (a -> b)
{fmap evert => <= fmap revert} {distribute => <= distribute}
a -> Ev g b
Let's assume the rigid law holds. We want to prove that fflip . flap = id
if and only if evert . revert = id
, so we must handle both directions:
Firstly, let's assume evert . revert = id
. The counterclockwise way of going around the square from a -> g b
to g (a -> b)
amounts to fflip
(see the definition of fflipEv
above). As the conterclockwise way is made out of three isomorphisms, it follows that fflip
has an inverse. Since flap
is its left inverse (by the rigid law), it must also be its inverse. Therefore fflip . flap = id
.
Secondly, let's assume fflip . flap = id
. Again, the counterclockwise way from a -> g b
to g (a -> b)
is fflip
, but now we know that it has an inverse, namely flap
. It follows that each of the functions composed to make up the counterclockwise way must have an inverse. In particular, revert
must have an inverse. Since evert
is its right inverse (by the rigid law), it must also be its inverse. Therefore, evert . revert = id
.
The results above allow us to precisely situate where Rigid
stands in relation to Distributive
. A rigid functor is a would-be distributive, except that it only follows the identity law of distributive, and not the composition one. Making fflip
an isomorphism, with flap
as its inverse, amounts to upgrading Rigid
to Distributive
.
Looking at fflip
and flap
from a monadic point of view, we might say that rigid monads are equipped with an injective conversion from Kleisli arrows to static arrows. With distributive monads, the conversion is upgraded to an isomorphism, which is a generalisation of how Applicative and Monad are equivalent for Reader.
extractors
condenses much of what Distributive
is about. For any distributive functor g
, there is a g (g a -> a)
value in which each position is filled with a matching g a -> a
extractor function. It seems accurate to say that when we move from Distributive
to Rigid
we lose this guarantee that position and extractor will match, and, with it, the ability to reconstruct an adequate functorial shape out of nothing. In this context, it is worth having a second look at the extractors
implementation for Sel
early in this answer. Any a -> r
function corresponds to a Sel r a -> a
extractor, which means there generally will be a myriad of extractors we can't enumerate, so we have to satisfy ourselves with non-isomorphic fflip
and infuse
(in hindsight, the const
that shows up in the implementation of extractors
already gives the game away). This feels a bit like the lack of a Traversable
instance for functions. (In that case, though, there is a way to cheat if the domain type of the function is enumerable, Data.Universe style. I'm not sure if there actually is such a workaround, however impractical, for Sel
.)
I obtained the results about the revert
isomorphism for Distributive
largely by mirroring how the shape-and-contents decomposition of Traversable
, the dual class, works. (A very readable paper that explores the shape-and-contents theme is Understanding Idiomatic Traversals Backwards and Forwards, by Bird et. al.). While covering that in more detail would probably be better left for a separate post, there is at least one question worth posing here: does a notion analogous to Rigid
make sense for Traversable
? I believe it does, albeit my feeling is that it sounds less useful than Rigid
might be. One example of a "co-rigid" pseudo-traversable would be a data structure equipped with a traversal that duplicates effects, but then discards the corresponding duplicate elements upon rebuilding the structure under the applicative layer, so that the identity law is followed -- but not the composition one.
Speaking of revert
, the Ev
construction is in itself quite meaningful: it is an encoding of the free distributive functor. In particular, evert
and revert
are comparable to liftF and retract for free monads, as well as to similar functions for other free constructions. (In such a context, revert
being a full inverse to evert
hints at how strong Distributive
is. It is more usual for the retraction to discard information in some cases, as it happens in the general case of Rigid
.)
Last, but not least, there is another way still of making sense of Ev
: it means the polymorphic extractor type represents the distributive functor, in the Representable sense, with evert
corresponding to index
, and revert
, to tabulate
. Unfortunately, the quantification makes it very awkward to express that in Haskell with the actual Representable
interface. (It is symptomatic that I had to reach for unsafeCoerce
to give Ev
its natural Rigid
and Distributive
instances.) If it serves as solace, it wouldn't be a terribly practical representation anyway: if I already have a polymorphic extractor in hands, I don't actually need index
for extracting values.
We are all familiar with the Traversable
typeclass, which can be boiled down to the following:
class Functor t => Traversable t
where
sequenceA :: Applicative f => t (f a) -> f (t a)
This makes use of the concept of an Applicative
functor. There is a laws-only strengthening of the categorical concept underlying Applicative
that goes like this:
-- Laxities of a lax monoidal endofunctor on Hask under (,)
zip :: Applicative f => (f a, f b) -> f (a, b)
zip = uncurry $ liftA2 (,)
husk :: Applicative f => () -> f ()
husk = pure
-- Oplaxities of an oplax monoidal endofunctor on ... (this is trivial for all endofunctors on Hask)
unzip :: Functor f => f (a, b) -> (f a, f b)
unzip fab = (fst <$> fab, snd <$> fab)
unhusk :: f () -> ()
unhusk = const ()
-- The class
class Applicative f => StrongApplicative f
-- The laws
-- zip . unzip = id
-- unzip . zip = id
-- husk . unhusk = id
-- unhusk . husk = id -- this one is trivial
The linked question and its answers have more details, but the gist is that StrongApplicative
s model some notion of "fixed size" for functors. This typeclass has an interesting connection to Representable
functors. For reference, Representable
is:
class Functor f => Representable x f | f -> x
where
rep :: f a -> (x -> a)
unrep :: (x -> a) -> f a
instance Representable a ((->) a)
where
rep = id
unrep = id
An argument by @Daniel Wagner shows that StrongApplicative
is a generalization of Representable
, in that every Representable
is StrongApplicative
. Whether there are any StrongApplicative
s that are not Representable
is not yet clear.
Now, we know that Traversable
is formulated in terms of Applicative
, and runs in one direction. Since StrongApplicative
promotes the Applicative
laxities to isomorphisms, perhaps we want to use this extra equiment to invert the distributive law that Traversable
supplies:
class Functor f => Something f
where
unsequence :: StrongApplicative f => f (t a) -> t (f a)
It just so happens that (->) a
is a StrongApplicative
, and in fact a representative specimen (if you'll pardon the pun) of the genus of Representable
StrongApplicative
functors. Hence we can write your inject
/promote
operation as:
promote :: Something f => (a -> f b) -> f (a -> b)
promote = unsequence
We mentioned before that StrongApplicative
is a superclass of the family of Representative
functors. From examining the type of unsequence
, it is obvious that the stronger a constraint we place on the polymorphic applicative, the easier it will be to implement unsequence
(and hence the more instances of the resulting class).
So in a sense there is a hierarchy of "detraversable" functors that flows in the opposite direction to a hierarchy of applicative effects with respect to which you might wish to detraverse them. The hierarchy of "inner" functors would go like this:
Functor f => Applicative f => StrongApplicative f => Representable x f
And the corresponding hierarchy of detraversable/distributive functors might go like this:
Distributive t <= ADistributive t <= SADistributive t <= RDistributive t
With definitions:
class RDistributive t
where
rdistribute :: Representable x f => f (t a) -> t (f a)
default rdistribute :: (SADistributive t, StrongApplicative f) => f (t a) -> t (f a)
rdistribute = sadistribute
class RDistributive t => SADistributive t
where
sadistribute :: StrongApplicative f => f (t a) -> t (f a)
default sadistribute :: (ADistributive t, Applicative f) => f (t a) -> t (f a)
sadistribute = adistribute
class SADistributive t => ADistributive t
where
adistribute :: Applicative f => f (t a) -> t (f a)
default adistribute :: (Distributive t, Functor f) => f (t a) -> t (f a)
adistribute = distribute
class ADistributive t => Distributive t
where
distribute :: Functor f => f (t a) -> t (f a)
Our definition of promote
can be generalized to depend on RDistributive
(since (->) a
itself is indeed a representable functor):
promote :: RDistributive f => (a -> f b) -> f (a -> b)
promote = rdistribute
In a strange turn of events, once you get down to the bottom of this hierarchy (i.e. to Distributive
), your promise of detraversability has become so strong relative to your demands that the only functors for which you can implement it are themselves Representable
. An example of such a distributive, representable (and hence rigid) functor is that of pairs:
data Pair a = Pair { pfst :: a, psnd :: a }
deriving Functor
instance RDistributive Pair
instance SADistributive Pair
instance ADistributive Pair
instance Distributive Pair
where
distribute x = Pair (pfst <$> x) (psnd <$> x)
Of course if you make a strong demand of the polymorphic "inner functor", for example Representable x f
in RDistributive
, instances like this become possible:
newtype Weird r a = Weird { runWeird :: (a -> r) -> a }
deriving Functor
instance RDistributive (Weird r)
where
rdistribute = fmap unrep . promoteWeird . rep
where
promoteWeird :: (x -> Weird r a) -> Weird r (x -> a)
promoteWeird f = fmap (. f) $ Weird $ \k m -> m `runWeird` \a -> k (const a)
TODO: Check where (if anywhere) in the hierarchy all the other examples of rigid functors fall.
As I said I haven't thought about it super carefully, so maybe the folks here that have devoted some thought to the rigid functor concept can immediately poke holes in it. Alternately, maybe it makes things fall into place that I can't yet see.
It's probably worthwhile thinking about some laws for these untraversing typeclasses. An obvious one that suggests itself is sequence . unsequence = id
and unsequence . sequence = id
wherever the functor supports both Traversable
and Untraverse
.
It's also worth mentioning that the interaction of "distributive law"s of functors with monads and comonads is quite well studied, so that might have some relevance to the monad related discussion in your posts.