Some instances of Category
are also instances of Functor
. For example:
{-# LANGUAGE ExistentialQuantification, TupleSections #-}
import Prelude hiding (id, (.))
import Control.Category
import Control.Arrow
data State a b = forall s. State (s -> a -> (s, b)) s
apply :: State a b -> a -> b
apply (State f s) = snd . f s
assoc :: (a, (b, c)) -> ((a, b), c)
assoc (a, (b, c)) = ((a, b), c)
instance Category State where
id = State (,) ()
State g t . State f s = State (\(s, t) -> assoc . fmap (g t) . f s) (s, t)
(.:) :: (Functor f, Functor g) => (a -> b) -> f (g a) -> f (g b)
(.:) = fmap . fmap
instance Functor (State a) where
fmap g (State f s) = State (fmap g .: f) s
instance Arrow State where
arr f = fmap f id
first (State f s) = State (\s (x, y) -> fmap (,y) (f s x)) s
Here arr f = fmap f id
for instance Arrow State
. Is this true for all instances of Category
which are also instances of Functor
? The type signatures are:
arr :: Arrow a => (b -> c) -> a b c
(\f -> fmap f id) :: (Functor (a t), Category a) => (b -> c) -> a b c
It seems to me that they should be equivalent.
Arrow
laws are enough to define a law-abidingFunctor
instance byinstance Arrow a => Functor (a s) where fmap f v = v >>> arr f
. Perhaps that together with parametricity is enough to ensure that this is also the only law-abiding instance, though I haven't worked out the details so I won't claim it to be true. – Lukerfmap
should equal(<<<)
. – GranoffFunctor
instance. So the answer to your question seems to be "yes". – Lukerarr
is a method ofArrow
, notCategory
, I am still somewhat skeptical - I doubt everyCategory
that also is aFunctor
needs to be anArrow
. The reverse is true, however, as everyArrow
gives not just aFunctor
, but anApplicative
. – DissertateCategory
that also is aFunctor
needs to be anArrow
" - indeed, though the underlying issue is thatarr
andfirst
are, as leftaroundabout says below, "quite separate things combined". – Davinadavine