[Haskell-cafe] Approach to generalising Functor, is it worth pursuing?

Clinton Mead clintonmead at gmail.com
Sun Oct 4 07:15:11 UTC 2015


I've been thinking about generalising Functor, as I had something which was
"Functor like" but didn't seem to fit into the existing definition. The
example I'll present isn't the problem I was trying to solve, but it
probably illustrates the solution better. The questions I have is:
1. Is this useful?
2. Has this been done?

If the answers are Yes and No, I'll continue on into making this into a
package.

Anyway, here's what I've done:

As we know, the type signature of fmap is the following:

fmap :: Functor f => (a -> b) -> (f a -> f b)

I've put brackets around the last two arguments to show that fmap can be
also seen as a function which takes a function and returns a new function,
in a different "space", for want of a better word.

fmap should also follow this rule:

fmap (f . g) == (fmap f . fmap g)

So we can map an ordinary function into the "Maybe" space, but in a way
that composing functions in the putting them in the space is the same as
putting them in the space then composing them.

I thought it would be nice if we could fmap to Kleisli Arrows, like so:

fmap :: Monad m => (a -> b) -> Kleisli m a b

Of course this is just "arr". But "arr" follows fmap's rules, so I thought
it would be nice to make it a functor.

So I was looking for more generalised versions of "Functor", and I found
the 'categories' package, which had the following definition:


class (Category
<https://hackage.haskell.org/package/base-4.7.0.1/docs/Control-Category.html#t:Category>
 r, Category
<https://hackage.haskell.org/package/base-4.7.0.1/docs/Control-Category.html#t:Category>
t)
=> Functor f r t | f r -> t, f t -> r where
  fmap :: r a b -> t (f a) (f b)

This solves half my problem, as now I can set r = (->) and t = Kleisli m
and I've got the categories right. But it forces the "output" category to
have a data constructor.

So:

fmap :: Monad m => (a -> b) -> Kleisli m a b

Just won't fit. I'd need to make it:

fmap :: Monad m => (a -> b) -> Kleisli m (Id a) (Id b)

and then unwrap the results. I found this ugly though.

So I've gone with another approached. I've linked the code here:
http://ideone.com/TEg4MN and also included it inline at the bottom of this
mail.

Defining functors now becomes a bit wordy, but basically what I've defined
is two functor instances. The first is just a copy of the existing functor
instances to maintain the status quo behaviour. But secondly I've defined
the Kleisli instance as discussed above.

The "main" line, does two calls to fmap. The outermost (on the left) is
just an ordinary fmap call on lists. The innermost, fmaps the function
"triple" into a Kleisli Arrow, allowing it to be composed with the the
Kleisli arrow already defined, 'evenOrNothing'. Type inference works this
all out magically without signatures being required.

Like I said, is approach new and useful? Improvements would be appreciated
also, I'm only over the last few months really started focusing on learning
Haskell properly (after leaving my previous job of 8 years), so I'm sure
I'm still doing plenty of things not quite right.

Thanks,

Clinton

---


{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}

module Main (
    main
) where

import qualified Control.Arrow
import Prelude hiding (Functor, fmap, (.))
import Control.Category (Category, (.))
import qualified Data.Functor
import qualified Control.Arrow
import Control.Arrow (Kleisli(Kleisli), runKleisli)

type family F (r :: (* -> * -> *)) (t :: (* -> * -> *)) x
type family InputParam f x
type family ResultParam f x
type family InputCategory f :: (* -> * -> *)
type family ResultCategory f :: (* -> * -> *)

class Functor f where
  fmap ::
    (
      Category r, Category t,
      f ~ F r t c, f ~ F r t d,
      r ~ InputCategory f, t ~ ResultCategory f,
      a ~ InputParam f c, b ~ InputParam f d,
      c ~ ResultParam f a, d ~ ResultParam f b
    ) =>
      r a b -> t c d


data OrdinaryFunctor :: (* -> *) -> *
type instance F (->) (->) (f a) = OrdinaryFunctor f
type instance InputParam (OrdinaryFunctor f) (f a) = a
type instance ResultParam (OrdinaryFunctor f) a = f a
type instance InputCategory (OrdinaryFunctor f) = (->)
type instance ResultCategory (OrdinaryFunctor f) = (->)

instance (Data.Functor.Functor f) => Functor (OrdinaryFunctor f) where
  fmap = Data.Functor.fmap

data KleisliFunctor :: (* -> *) -> *
type instance F (->) (Kleisli m) a = KleisliFunctor m
type instance InputParam (KleisliFunctor f) a = a
type instance ResultParam (KleisliFunctor m) a = a
type instance InputCategory (KleisliFunctor m) = (->)
type instance ResultCategory (KleisliFunctor m) = Kleisli m

instance (Monad m) => Functor (KleisliFunctor m) where
  fmap = Control.Arrow.arr

triple = (*3)
evenOrNothing = Kleisli (\x -> if (even x) then Just x else Nothing)

main = print $ fmap (runKleisli (evenOrNothing . fmap triple)) [3..6]
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20151004/1d52f8b0/attachment.html>


More information about the Haskell-Cafe mailing list