Is this property of a functor stronger than a monad?

前端 未结 3 2098
礼貌的吻别
礼貌的吻别 2020-12-04 17:07

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) 
3条回答
  •  囚心锁ツ
    2020-12-04 17:26

    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.)

    A place in the constellation

    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.

    Miscellaneous remarks

    • 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.

提交回复
热议问题