Have you seen this functor/contrafunctor combo?

newtype Q p a = Q (p a -> a)
instance ContraFunctor p => Functor (Q p) where fmap h (Q w) = Q (h . w . cmap h)
using "cmap" for contravariant map. For instance, p a = u -> a.
instance ContraFunctor p => Applicative (Q p) where pure a = Q (pure a) Q fs <*> Q as = Q (\ r -> let f = fs (cmap ($ a) r) a = as (cmap (f $) r) in f a)
I've checked the functor laws but not the applicative laws, and I haven't looked for a Monad instance. Or extend to a more symmetric definition adding a (covariant) functor f to the contravariant functor p.
newtype Q' p f a = Q' (p a -> f a)
A (law-abiding) Functor instance is easy, but I don't know about an Applicative instance. Have you seen Q or Q' before? They look like they ought to be something familiar & useful. -- Conal

If there would be a package where this could be in it would be contravariant[1], but it isn't.
newtype Q' p f a = Q' (p a -> f a)
This compiles:
instance (Contravariant p, Functor m, MonadFix m) => Applicative (Q' p m) where pure a = Q' (pure (return a)) Q' fs <*> Q' as = Q' $ \r -> do rec f <- fs (contramap ($ a) r) a <- as (contramap (f $) r) return $ f a
[1] http://hackage.haskell.org/package/contravariant -- Sjoerd Visscher https://github.com/sjoerdvisscher/blog

Oh, yeah. Thanks, Sjoerd.
I wonder if there's some way not to require Monad. Some sort of
ApplicativeFix instead. Hm.
-- Conal
On Wed, Jun 6, 2012 at 2:43 PM, Sjoerd Visscher
If there would be a package where this could be in it would be contravariant[1], but it isn't.
newtype Q' p f a = Q' (p a -> f a)
This compiles:
instance (Contravariant p, Functor m, MonadFix m) => Applicative (Q' p m) where pure a = Q' (pure (return a)) Q' fs <*> Q' as = Q' $ \r -> do rec f <- fs (contramap ($ a) r) a <- as (contramap (f $) r) return $ f a
[1] http://hackage.haskell.org/package/contravariant
-- Sjoerd Visscher https://github.com/sjoerdvisscher/blog

On Jun 7, 2012, at 5:21 PM, Conal Elliott wrote:
Oh, yeah. Thanks, Sjoerd.
I wonder if there's some way not to require Monad. Some sort of ApplicativeFix instead. Hm.
Something like this:
instance (Contravariant p, ApplicativeFix f) => Applicative (Q' p f) where pure a = Q' (pure (pure a)) Q' fs <*> Q' as = Q' $ \r -> uncurry ($) <$> afix (\ ~(f, a) -> (,) <$> fs (contramap ($ a) r) <*> as (contramap (f $) r))
This works with this ApplicativeFix class:
class Applicative f => ApplicativeFix f where afix :: (a -> f a) -> f a
At first I thought there would be no instance for this that would not also be a monad. But actually the list instance for MonadFix looks more like an instance for ZipList:
mfix (\x -> [1:1:zipWith (+) x (tail x), 1:zipWith (+) x x])
gives [[1,1,2,3,5,8…], [1,2,4,8,16,32,64…]], and mfix (\x -> [f x, g x, h x]) = [fix f, fix g, fix h]. For a list monad instance I would expect results with a mixture of f, g and h (but that would not be productive). Btw, you've asked this before and you got an interesting response: http://haskell.1045720.n5.nabble.com/recursive-programming-in-applicative-fu... -- Sjoerd Visscher https://github.com/sjoerdvisscher/blog
participants (2)
-
Conal Elliott
-
Sjoerd Visscher