[Haskell-cafe] Functions of type foo :: f a -> g a

Edward Kmett ekmett at gmail.com
Tue May 11 14:27:19 EDT 2010


On Tue, May 11, 2010 at 2:01 PM, Gordon J. Uszkay <uszkaygj at mcmaster.ca>wrote:

> I would like to build a class that includes a method to move data from one
> arbitrary functor to another, a natural transformation.   The structures
> might be more than just functors, but I can start with that.  I ran into
> some practical issues with resolving the type variables for my
> multiparameter type class, which I can resolve with functional dependencies.
>   I can also not isolate the natural transformation from my overall
> operation, muddling it with the element transformation.  I was wondering if
> anyone had any words of advice, example  or warning about this kind of
> function or method in general?
>
> Class (Functor f, Functor g) => Foo f g a where
>  foo :: f a -> g a
>  bar :: (a->b) -> g a -> g b
>

In general I would shy away from encoding natural transformations as a
typeclass describing one family of morphisms of the form f a -> g a. I would
avoid it because the choice of function f a -> g a isn't really canonical.
There are many potentially valid such functions.

foo :: Maybe a -> [a]
foo (Just a) = [a]
foo Nothing = []

bar :: Maybe a -> [a]
bar (Just a) = repeat a
bar Nothing = []

baz :: Maybe a -> [a]
baz _ = Nothing

quux n :: Int -> Maybe a -> [a]
quux (Just a) = replicate a n
quux Nothing = Nothing

With that in mind an arguably better approach would be to define a natural
transformation as:

type Nat f g = forall a. f a -> g a

or even

type f :~> g = forall a. f a -> g a

and pass them around explicitly then you can encode things like:

hylo<http://hackage.haskell.org/packages/archive/category-extras/0.53.5/doc/html/Control-Morphism-Hylo.html#v%3Ahylo>::
Functor<http://hackage.haskell.org/packages/archive/base/4.2.0.1/doc/html/Control-Monad.html#t%3AFunctor>f
=>
Algebra<http://hackage.haskell.org/packages/archive/category-extras/0.53.5/doc/html/Control-Functor-Algebra.html#t%3AAlgebra>g
b -> (f
:~><http://hackage.haskell.org/packages/archive/category-extras/0.53.5/doc/html/Control-Functor-Extras.html#t%3A%3A%7E%3E>g)
->
Coalgebra<http://hackage.haskell.org/packages/archive/category-extras/0.53.5/doc/html/Control-Functor-Algebra.html#t%3ACoalgebra>f
a -> a -> b

hylo f e g = f . e . fmap (hylo f e g). g

This is important because there can exist such natural transformations that
need data out of your current environment: i.e. the natural transformation
((,) x), the quux example above, etc.

-Edward Kmett
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20100511/0dcf39b4/attachment.html


More information about the Haskell-Cafe mailing list