Are the "natural transformations" we apply on Coyoneda to get a Functor actually "natural transformations"?

时间:2015-07-31 20:22:47

标签: haskell category-theory

I have a theoretical question about the nature of a type that is used in a lot of examples explaining the Coyoneda lemma. They are usually referred to as "natural transformations" which to my knowledge mappings between functors. What puzzles me is that in these examples they sometimes map from Set to some functor F. So it does not really semm to be a mapping between functors but something a little more relaxed.

Here is the code in question:

{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
module Coyo where

import           Data.Set (Set)
import qualified Data.Set as Set

data Coyoneda f a where
  Coyoneda :: (b -> a) -> f b -> Coyoneda f a

instance Functor (Coyoneda f) where
  fmap f (Coyoneda c fa) =  Coyoneda (f . c) fa

set :: Set Int
set = Set.fromList [1,2,3,4]

lift :: f a -> Coyoneda f a
lift fa = Coyoneda id fa

lower :: Functor f => Coyoneda f a -> f a
lower (Coyoneda f fa) = fmap f fa

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

coyoset :: Coyoneda Set Int
coyoset = fmap (+1) (lift set)

applyNatT :: NatT f g -> Coyoneda f a -> Coyoneda g a
applyNatT n (Coyoneda f fa) = Coyoneda f (n fa)

-- Set.toList is used as a "natural transformation" here
-- while it conforms to the type signature of NatT, it
-- is not a mapping between functors `f` and `g` since
-- `Set` is not a functor.
run :: [Int]
run = lower (applyNatT Set.toList coyoset)

What am I misunderstanding here?

EDIT: After a discussion on #haskell in freenode I think I need to clarify my question a little. It's basically: "What is Set.toList in a category theoretic sense? Since it is obviously(?) not a natural transformation".

1 个答案:

答案 0 :(得分:13)

要使n成为Haskell中的自然变换,它需要服从(对于所有f

(fmap f) . n == n . (fmap f)

Set.toList不是这种情况。

fmap (const 0) . Set.toList        $ Set.fromList [1, 2, 3] = [0, 0, 0]
Set.toList     . Set.map (const 0) $ Set.fromList [1, 2, 3] = [0]
相反,它遵循一套不同的法律。还有另一种转换n',以便以下方式保持

n' . (fmap f) . n == fmap f

如果我们选择f = id并应用仿函数法fmap id == id,我们可以看到这意味着n' . n == id,因此我们有类似的公式:

(fmap f) . n' . n == n' . (fmap f) . n == n' . n . (fmap f)

n = Set.toListn' = Set.fromList遵守此法律。

Set.map (const 0) . Set.fromList   . Set.toList        $ Set.fromList [1, 2, 3] = fromList [0]
Set.fromList      . fmap (const 0) . Set.toList        $ Set.fromList [1, 2, 3] = fromList [0]
Set.fromList      . Set.toList     . Set.map (const 0) $ Set.fromList [1, 2, 3] = fromList [0]

除了观察Set是列表的等价类之外,我不知道我们可以称之为什么。 Set.toList找到等价类的代表成员,Set.fromList是商。

值得注意的是Set.fromList是一种自然的转变。至少它位于 Hask 的合理子类别中,其中a == b暗示f a == f b(此处==Eq相等)。这也是 Hask 的子类别,其中Set是一个仿函数;它不包括degenerate things like this

leftaroundabout还指出Set.toList Hask 子类别的自然转换,其中态射被限制为injective functions where f a == f b implies a == b