Can `Fix` and `(,)` be seen as functors in some sense? - haskell

I've been wondering what a complete, all-encompassing context for instance Functor (f :.: g) would be. The immediate thought that pops into my head is:
newtype (f :.: g) a = Comp (f (g a))
instance (Functor f, Functor g) => Functor (f :.: g) where
fmap f (Comp x) = Comp (fmap (fmap f) x)
But then, two contravariant functors would also compose to be covariant, like so:
instance (Contravariant f, Contravariant g) => Functor (f :.: g) where
fmap f (Comp x) = Comp (contramap (contramap f) x)
Already not a promising beginning. However, I've also noticed that technically, f and g don't even have to have kind * -> * -- the only requirement for f :.: g :: * -> * is that f :: k -> * and g :: * -> k for some k. This means that non-functor types could compose to be functors, e.g.
newtype Fix f = Fix (f (Fix f))
instance Functor (Fix :.: (,)) where
fmap f (Comp x) = Comp (go x) where
go (Fix (x,xs)) = Fix (f x,go xs)
Fix :.: (,) is isomorphic to the Stream type:
data Stream a = a :> Stream a
so this does seem to be a non-trivial issue. This got me thinking -- if Haskell's Functor typeclass represents categorical functors from Hask to Hask, does that mean types like Fix and (,) could be functors working on some other categories? What would those categories be?

Yes, and we can read off exactly what sense that is from the shape of the constructor. Let's look at (,) first.
The (,) Functor
(,) :: * -> * -> *
This takes two types and produces a type. Up to isomorphism, this is equivalent to
(,) :: (*, *) -> *
i.e. we might as well uncurry the function and take both arguments at once. So (,) can be viewed as a functor for Hask × Hask to Hask, where Hask × Hask is the product category. We have a word for a functor whose domain is the product of two categories. We call it a bifunctor, and it's actually in base Haskell. Specifically, a bifunctor p is capable of turning maps from (a, b) to (a', b') in the product category into maps from p a b to p a' b'. Haskell's typeclass writes this in a slightly different but equivalent way
bimap :: Bifunctor p => (a -> b) -> (c -> d) -> p a c -> p b d
Having a map a -> b and a map c -> d is exactly equivalent to having a map (a, c) -> (b, d) in the product category. (What I mean by that is: the maps (a, c) -> (b, d) in the product category are defined to be products of maps a -> b and c -> d).
The Fix Functor
We can deal with Fix the same way.
newtype Fix f = Fix (f (Fix f))
Its shape is
Fix :: (* -> *) -> *
It takes a one-argument type constructor and produces a type.
Now, in Haskell, the * -> * part can be any one-argument type constructor, but categorically it's much nicer to work with functors. So I'm going to make the slightly stronger constraint (which it turns out we'll need in a minute) that the * -> * argument to Fix is a Functor, i.e. a functor from Hask to Hask.
In that case, Fix has the right shape to be a functor from the functor category Hask ^ Hask to the category Hask. A functor, categorically, takes objects to objects and arrows to arrows. So let's take that one step at a time.
The object part is easy, we've already defined it. Specifically, Fix takes the functor f (functors are the objects of a functor category; read that again if it doesn't make sense yet) and maps it to the type Fix f that we just defined.
Now, the arrows of a functor category are natural transformations. Given two functors f, g :: C -> D, a natural transformation α from f to g is a mapping from the objects of C to the arrows of D. Specifically, for every object x in the category C, α x should be an arrow in D going from f x to g x, with the following coherence condition:
For every arrow h : x -> y in C, we must have (g h) . (α x) === (α y) . (f h)
(Using notation such as function composition very loosely, in true category theory spirit)
Drawn as a commutative diagram, the following must commute,
Haskell doesn't really have a built-in type for natural transformations. With Rank-N types, we can write the correct shape
(forall a. f a -> g a)
This is the shape of a natural transformation, but of course we haven't verified the coherence property. So we'll just have to trust that it satisfies that property.
With all of this abstract nonsense in mind, if Fix is going to be a functor from Hask ^ Hask to Hask, it should take a natural transformation to an ordinary Haskell function, and it should have the following shape.
fixmap :: (Functor f, Functor g) => (forall a. f a -> g a) -> Fix f -> Fix g
Once we have this type, we can write the implementation fairly easily.
fixmap h (Fix inner) = Fix (h . fmap (fixmap h) $ inner)
or, equivalently (by the rules of natural transformations),
fixmap h (Fix inner) = Fix (fmap (fixmap h) . h $ inner)
I'm not aware of an idiomatic name for this shape of functor, nor am I aware of a typeclass that encompasses it, but of course nothing stops you from making it yourself.

Related

Is there a corresponding optic for higher-order traversable functors?

Hedgehog has an HTraversable class defined like this:
-- | Higher-order traversable functors.
--
class HTraversable t where
htraverse :: Applicative f => (forall a. g a -> f (h a)) -> t g -> f (t h)
Which is used with their Var type for parameterizing a type over whether values are concrete or abstract. t has kind (* -> *) -> * and is a higher order functor although they don't actually have that class, f, g and h have kind * -> *. I've seen the same thing defined in a few different libraries.
Is there a way to get an optic out of this? I confess I don't know what that would even do, and I'm not super comfortable with lenses or regular Traversable either.
Sure.
type HTraversal s t a b =
forall f. Applicative f => (forall x. a x -> f (b x)) -> s -> f t
htraverse :: HTraversable t => HTraversal (t a) (t b) a b
Remember, lens's Traversal comes about by taking the type of traverse and letting the t a and t b types vary, viewing the traversable not as a polymorphic container but as a monolithic blob.
How useful HTraversal is, I dunno. You can't compose them nicely with (.).

fmapping arrows over monads

I understand that an Arrow is a Profunctor, where one can transform its input and its output, but can one map an arrow over a Functor?
I understand that as-asked the answer is "no", since the fmap function type signature is (a -> b) -> f a -> f b and does not admit Arrow a b, but I hope what I'm asking is clear.
I am looking for a way to, for example, transform a Maybe input with an Arrow, where Nothing goes to Nothing and Just x goes to Just y where y is the result of applying the Arrow to x.
Arrow combines two concepts. One of them, as you say, is that of a profunctor, but first of all it's just a specific class of categories (as indeed the superclass evidences).
That's highly relevant for this question: yes, the signature of fmap is (a -> b) -> f a -> f b, but actually that is not nearly the full generality of what a functor can do! In maths, a functor is a mapping between two categories C and D, that assigns each arrow in C to an arrow in D. Arrows in different categories, that is! The standard Functor class merely captures the simplest special case, that of endofunctors in the Hask category.
The full general version of the functor class actually looks more like this (here my version from constrained-categories):
class (Category r, Category t) => Functor f r t | f r -> t, f t -> r where
fmap :: r a b -> t (f a) (f b)
Or, in pseudo-syntax,
class (Category (──>), Category (~>)) => Functor f (──>) (~>) where
fmap :: (a ──> b) -> f a ~> f b
This can sure enough also work when one of the categories is a proper arrow rather than an ordinary function category. For instance, you could define
instance Functor Maybe (Kleisli [] (->)) (Kleisli [] (->)) where
fmap (Kleisli f) = Kleisli mf
where mf Nothing = [Nothing]
mf (Just a) = Just <$> f a
to be used like
> runKleisli (fmap . Kleisli $ \i -> [0..i]) $ Nothing
[Nothing]
> runKleisli (fmap . Kleisli $ \i -> [0..i]) $ Just 4
[Just 0,Just 1,Just 2,Just 3,Just 4]
Not sure whether this would be useful for anything nontrivial, if using the standard profunctor-ish arrows. It is definitely useful in other categories which are not Hask-profunctors, for instance
instance (TensorSpace v) => Functor (Tensor s v) (LinearFunction s) (LinearFunction s)
expressing that you can map a linear function over a single factor of a tensor product (whereas it's generally not possible to map a nonlinear function over such a product – the result would depend on a choice of basis on the vector space).
I am looking for a way to, for example, transform a Maybe input with an arrow, where Nothing goes to Nothing and Just x goes to Just y where y is the result of applying the Arrow to x.
This can be implemented for specific Functors (such as Maybe), though ArrowChoice will likely be necessary:
maybeAmap :: ArrowChoice p => p a b -> p (Maybe a) (Maybe b)
maybeAmap p =
maybe (Left ()) Right
^>> returnA +++ p
>>^ const Nothing ||| Just
See Arrow equivalent of mapM? for a similar function written in proc-notation.
Speaking of mapM, profunctors has an interesting class called Traversing:
-- Abbreviated class definition:
class (Choice p, Strong p) => Traversing p where
traverse' :: Traversable f => p a b -> p (f a) (f b)
wander :: (forall f. Applicative f => (a -> f b) -> s -> f t) -> p a b -> p s t
The flag-bearer instance of Traversing is the one for the Star profunctor, which provides an alternative encoding of the familiar traverse function. Note that, while leftaroundabout's answer demonstrates a non-Hask functor for categories which are not necessarily Hask-profunctors, with Traversing we have a construction for Profunctors that do not necessarily have a Category instance.

Make Data Type of Kind * -> * That's Not a Functor

Brent Yorgey's Typeclassopedia gives the following exercise:
Give an example of a type of kind * -> * which cannot be made an
instance of Functor (without using undefined).
Please tell me what "cannot be made an instance of Functor" means.
Also, I'd appreciate an example, but perhaps as a spoiler so that you can, please, guide me to the answer.
Let's talk about variances.
Here's the basic notion. Consider the type A -> B. What I want you to imagine is that such a type is similar to "having a B" and also "owing an A". In fact, if you pay back your A you immediately receive your B. Functions are kind of like escrow in that way.
The notion of "having" and "owing" can extend to other types. For instance, the simplest container
newtype Box a = Box a
behaves like this: if you "have" a Box a then you also "have" an a. We consider types which have kind * -> * and "have" their argument to be (covariant) functors and we can instantiate them to Functor
instance Functor Box where fmap f (Box a) = Box (f a)
What happens if we consider the type of predicates over a type, like
newtype Pred a = Pred (a -> Bool)
in this case, if we "have" a Pred a, we actually "owe" an a. This arises from the a being on the left side of the (->) arrow. Where fmap of Functor is defined by passing the function into the container and applying it to all the places where we "have" our inner type, we can't do the same for Pred a since we don't "have" and as.
Instead, we'll do this
class Contravariant f where
contramap :: (a -> b) -> (f b -> f a)
Now that contramap is like a "flipped" fmap? It will allow us to apply the function to the places where we "own" a b in Pred b in order to receive a Pred a. We might call contramap "barter" because it encodes the idea that if you know how to get bs from as then you can turn a debt of bs into a debt of as.
Let's see how it works
instance Contravariant Pred where
contramap f (Pred p) = Pred (\a -> p (f a))
we just run our trade using f prior to passing it on into the predicate function. Wonderful!
So now we have covariant and contravariant types. Technically, these are known as covariant and contravariant "functors". I'll also state immediately that almost always a contravariant functor is not also covariant. This, thus, answers your question: there exist a bunch of contravariant functors which are not able to be instantiated to Functor. Pred is one of them.
There are tricky types which are both contravariant and covariant functors, though. In particular, the constant functors:
data Z a = Z -- phantom a!
instance Functor Z where fmap _ Z = Z
instance Contravariant Z where contramap _ Z = Z
In fact, you can essentially prove that anything which is both Contravariant and Functor has a phantom parameter.
isPhantom :: (Functor f, Contravariant f) => f a -> f b -- coerce?!
isPhantom = contramap (const ()) . fmap (const ()) -- not really...
On the other hand, what happens with a type like
-- from Data.Monoid
newtype Endo a = Endo (a -> a)
In Endo a we both owe and receive an a. Does that mean we're debt free? Well, no, it just means that Endo wants to be both covariant and contravariant and does not have a phantom parameter. The result: Endo is invariant and can instantiate neither Functor nor Contravariant.
A type t of kind * -> * can be made an instance of Functor if and only if it is possible to implement a law-abiding instance of the Functor class for it. So that means you have to implement the Functor class, and your fmap has to obey the Functor laws:
fmap id x == x
fmap f (fmap g x) == fmap (f . g) x
So basically, to solve this, you have to name some type of your choice and prove that there's no lawful implementation of fmap for it.
Let's start with a non-example, to set the tone. (->) :: * -> * -> * is the function type constructor, as seen in function types like String -> Int :: *. In Haskell, you can partially apply type constructors, so you can have types like (->) r :: * -> *. This type is a Functor:
instance Functor ((->) r) where
fmap f g = f . g
Intuitively, the Functor instance here allows you to apply f :: a -> b to the return value of a function g :: r -> a "before" (so to speak) you apply g to some x :: r. So for example, if this is the function that returns the length of its argument:
length :: [a] -> Int
...then this is the function that returns twice the length of its argument:
twiceTheLength :: [a] -> Int
twiceTheLength = fmap (*2) length
Useful fact: the Reader monad is just a newtype for (->):
newtype Reader r a = Reader { runReader :: r -> a }
instance Functor (Reader r) where
fmap f (Reader g) = Reader (f . g)
instance Applicative (Reader r) where
pure a = Reader (const a)
Reader f <*> Reader a = Reader $ \r -> f r (a r)
instance Monad (Reader r) where
return = pure
Reader f >>= g = Reader $ \r -> runReader g (f r) r
Now that we have that non-example out of the way, here's a type that can't be made into a Functor:
type Redaer a r = Redaer { runRedaer :: r -> a }
-- Not gonna work!
instance Functor (Redaer a) where
fmap f (Redaer g) = ...
Yep, all I did is spell the name backwards, and more importantly, flip the order of the type parameters. I'll let you try and figure out why this type can't be made an instance of Functor.

Can two non-functors compose to a functor?

We can have two types f, g :: * -> * such that they're not monads, but their composition is. For example for an arbitrary fixed s:
f a := s -> a
g a := (s, a)
g a isn't a monad (unless we restrict s to a monoid), but f (g a) is the state monad s -> (s, a). (Unlike functors and applicative functors, even if both f and g were monads, their composition might not be.)
Is there a similar example for functors or applicative functors? That is that the composition of f and g is a a functor (or an applicative functor), even though
one of f and g isn't an (applicative) functor and the other is, or
neither of them is an (applicative) functor,
This is not a (covariant) functor
f x = x -> r
but f . f is the "continuation" functor (also a monad):
f (f x) = (x -> r) -> r
This is probably not the best example because f is a contravariant functor.
Let g :: *->*. Then Const A . g is a functor for any A, in fact isomorphic to Const A.

What are the adjoint functor pairs corresponding to common monads in Haskell?

In category theory, a monad can be constructed from two adjoint functors. In particular, if C and D are categories and F : C --> D and G : D --> C are adjoint functors, in the sense that there is a bijection
hom(FX,Y) = hom(X,GY)
for each X in C and Y in D then the composition G o F : C --> C is a monad.
One such pair of adjoint functors can be given by fixing a type b and taking F and G to be
data F b a = F (a,b)
data G b a = G (b -> a)
instance Functor (F b) where
fmap f (F (a,b)) = F (f a, b)
instance Functor (G b) where
fmap f (G g) = G (f . g)
and the bijection between hom-sets is given (modulo constructors) by currying:
iso1 :: (F b a -> c) -> a -> G b c
iso1 f = \a -> G $ \b -> f (F (a,b))
iso2 :: (a -> G b c) -> F b a -> c
iso2 g = \(F (a,b)) -> let (G g') = g a in g' b
in which case the corresponding monad is
data M b a = M { unM :: b -> (a,b) }
instance Monad (M b) where
return a = M (\b -> (a,b))
(M f) >>= g = M (\r -> let (a,r') = f r in unM (g r') a)
I don't know what the name for this monad should be, except that it seems to be something like a reader monad that carries around a piece of over-writeable information (edit: dbaupp points out in the comments that this is the State monad.)
So the State monad can be "decomposed" as the pair of adjoint functors F and G, and we could write
State = G . F
So far, so good.
I'm now trying to figure out how to decompose other common monads into pairs of adjoint functors - for example Maybe, [], Reader, Writer, Cont - but I can't figure out what the pairs of adjoint functors that we can "decompose" them into are.
The only simple case seems to be the Identity monad, which can be decomposed into any pair of functors F and G such that F is inverse to G (in particularly, you could just take F = Identity and G = Identity).
Can anyone shed some light?
What you're looking for is Kleisli category. It was originally developed to show that every monad can be constructed from two adjoint functors.
The problem is that Haskell Functor is not a generic functor, it's an endo-functor in the Haskell category. So we need something different (AFAIK) to represent functors between other categories:
{-# LANGUAGE FunctionalDependencies, KindSignatures #-}
import Control.Arrow
import Control.Category hiding ((.))
import qualified Control.Category as C
import Control.Monad
class (Category c, Category d) => CFunctor f c d | f -> c d where
cfmap :: c a b -> d (f a) (f b)
Notice that if we take -> for both c and d we get an endo-functor of the Haskell category, which is just the type of fmap:
cfmap :: (a -> b) -> (f a -> f b)
Now we have explicit type class that represents functors between two given categories c and d and we can express the two adjoint functors for a given monad. The left one maps an object a to just a and maps a morphism f to (return .) f:
-- m is phantom, hence the explicit kind is required
newtype LeftAdj (m :: * -> *) a = LeftAdj { unLeftAdj :: a }
instance Monad m => CFunctor (LeftAdj m) (->) (Kleisli m) where
cfmap f = Kleisli $ liftM LeftAdj . return . f . unLeftAdj
-- we could also express it as liftM LeftAdj . (return .) f . unLeftAdj
The right one maps an object a to object m a and maps a morphism g to join . liftM g, or equivalently to (=<<) g:
newtype RightAdj m a = RightAdj { unRightAdj :: m a }
instance Monad m => CFunctor (RightAdj m) (Kleisli m) (->) where
cfmap (Kleisli g) = RightAdj . join . liftM g . unRightAdj
-- this can be shortened as RightAdj . (=<<) g . unRightAdj
(If anybody know a better way how to express this in Haskell, please let me know.)
Maybe comes from the free functor into the category of pointed sets and the forgetful functor back
[] comes from the free functor into the category of monoids and the forgetful functor back
But neither of these categories are subcategories of Hask.
As you observe, every pair of adjoint functors gives rise to a monad. The converse holds too: every monad arises in that way. In fact, it does so in two canonical ways. One is the Kleisli construction Petr describes; the other is the Eilenberg-Moore construction. Indeed, Kleisli is the initial such way and E-M the terminal one, in a suitable category of pairs of adjoint functors. They were discovered independently in 1965. If you want the details, I highly recommend the Catsters videos.

Resources