
Hi. I need map equivalent for Bijection type which is defined in fclabels: data Bijection (~>) a b = Bij { fw :: a ~> b, bw :: b ~> a } instance Category (~>) => Category (Bijection (~>)) where ... I can define this function as follows: mapBij :: Bijection (->) a c -> Bijection (->) [a] [b] -> Bijection (->) [a] [c] mapBij b1 b = (map (fw b1)) `Bij` (map (bw b1)) but do I really need to do it explicitly? Can I obtain same result using some Category combinators or other common stuff? Sergey

If you remove the second argument (which you don't use), you have the
function `liftBij` that is in fclabels.
Erik
On Mon, Aug 27, 2012 at 3:55 PM, Sergey Mironov
Hi. I need map equivalent for Bijection type which is defined in fclabels:
data Bijection (~>) a b = Bij { fw :: a ~> b, bw :: b ~> a }
instance Category (~>) => Category (Bijection (~>)) where ...
I can define this function as follows: mapBij :: Bijection (->) a c -> Bijection (->) [a] [b] -> Bijection (->) [a] [c] mapBij b1 b = (map (fw b1)) `Bij` (map (bw b1))
but do I really need to do it explicitly? Can I obtain same result using some Category combinators or other common stuff?
Sergey
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi, Sergey Mironov wrote:
I need map equivalent for Bijection type which is defined in fclabels:
data Bijection (~>) a b = Bij { fw :: a ~> b, bw :: b ~> a }
instance Category (~>) => Category (Bijection (~>)) where ...
I can define this function as follows: mapBij :: Bijection (->) a c -> Bijection (->) [a] [b] -> Bijection (->) [a] [c] mapBij b1 b = (map (fw b1)) `Bij` (map (bw b1))
Two observations. First observation: The second argument seems unnecessary, so we have the following instead:
mapBij :: Bijection (->) a c -> Bijection (->) [a] [c] mapBij b = (map (fw b)) `Bij` (map (bw b))
Second observation: I guess this works for arbitrary functors, not just lists, so we get the following:
fmapBij :: Functor f => Bijection (->) a c -> Bijection (->) (f a) (f c) fmapBij b = (fmap (fw b)) `Bij` (fmap (bw b))
Lets check that fmapBij returns a bijection:
fw (fmapBij b) . bw (fmapBij b) {- unfolding -} = fmap (fw b) . fmap (bw b) {- functor -} = fmap (fw b . bw b) {- bijection -} = fmap id {- functor -} = id
Looks good. I guess we can generalize this to get: If f is a functor on a category c, it is also a functor on the category (Bijection c). But I am not sure how to express this with Haskell typeclasses. Maybe along the lines of:
import Control.Categorical.Functor -- package categories
instance Endofunctor f cat => Endofunctor f (Bijection cat) where fmap b = (fmap (fw b)) `Bij` (fmap (bw b))
So Bijection is a functor in the category of categories? Tillmann

Yes, you are right, I don't really need the second argument. I am not
skilled enough to join the discussion, but I do understand your
solution. Thanks!
Sergey
2012/8/27 Tillmann Rendel
Hi,
Sergey Mironov wrote:
I need map equivalent for Bijection type which is defined in fclabels:
data Bijection (~>) a b = Bij { fw :: a ~> b, bw :: b ~> a }
instance Category (~>) => Category (Bijection (~>)) where ...
I can define this function as follows: mapBij :: Bijection (->) a c -> Bijection (->) [a] [b] -> Bijection (->) [a] [c] mapBij b1 b = (map (fw b1)) `Bij` (map (bw b1))
Two observations.
First observation: The second argument seems unnecessary, so we have the following instead:
mapBij :: Bijection (->) a c -> Bijection (->) [a] [c] mapBij b = (map (fw b)) `Bij` (map (bw b))
Second observation: I guess this works for arbitrary functors, not just lists, so we get the following:
fmapBij :: Functor f => Bijection (->) a c -> Bijection (->) (f a) (f c) fmapBij b = (fmap (fw b)) `Bij` (fmap (bw b))
Lets check that fmapBij returns a bijection:
fw (fmapBij b) . bw (fmapBij b) {- unfolding -} = fmap (fw b) . fmap (bw b) {- functor -} = fmap (fw b . bw b) {- bijection -} = fmap id {- functor -} = id
Looks good.
I guess we can generalize this to get: If f is a functor on a category c, it is also a functor on the category (Bijection c). But I am not sure how to express this with Haskell typeclasses. Maybe along the lines of:
import Control.Categorical.Functor -- package categories
instance Endofunctor f cat => Endofunctor f (Bijection cat) where fmap b = (fmap (fw b)) `Bij` (fmap (bw b))
So Bijection is a functor in the category of categories?
Tillmann
participants (3)
-
Erik Hesselink
-
Sergey Mironov
-
Tillmann Rendel