4
votes

tl;dr

Given the similarity between ixmap's signature and contramap's signature, I'd like to understand if Array i e is a contravariant functor in its first type argument or, at least, how the two things relate to each other from a category theory standpoint.

Longer lucubration

At the end of Chapter 12 from Real World Haskell, the function ixmap is used.

Based on its signature

ixmap :: (Ix i, Ix j) => (i, i) -> (i -> j) -> Array j e -> Array i e

I couldn't help but notice that, once we partially apply it to the first argument, e.g. we pass to it (1 :: Int, 1 :: Int) for simplicity, its signature becomes

ixmap (1 :: Int,1 :: Int) :: Ix j => (Int -> j) -> Array j e -> Array Int e

which has some similarity with the signature of contramap:

contramap :: (a' -> a) -> f a -> f a'

and even more with the specialization of it for Op:

contramap :: (a' -> a0) -> Op a a0 -> Op a a'

After all, I think, the type Array j e can be though of as the type of a function mapping a subset of type j to type e, kind of j -> a with a "restricted" j. So, just like b -> a is a Functor in a and Op a b was defined to make it a contravariant functor in b, I thought I could similarly define:

newtype Array' e i = Array' { arr :: Array i e }

and write a Contravariant instance for it:

instance Contravariant (Array' e) where
  contramap f a = undefined -- ???

What disturbs me is that I can't really use a partially applied ixmap for contramap because (1) what I do partially apply it to? And (2) doing it would block the i type (e.g. to Int in my example).

And I can't even think of a way for contrampa to retrie the required object of type (i,i) from the other two arguments f :: (i -> j) and a :: Array j e, because I have no function to go from j to i.

1
There is an additional issue: the Ix i constraint prevents the definition of contramap since the latter does not allow constraints. This is the same issue which prevents Functor Set, for instance, where we cannot add Ord as a requirement. I guess you will need a "constrained contravariant functor" typeclass, distinct from Contravariant. - chi
@chi I guess this is a good explanation of you point? - Enlico
Yes, that's the point. - chi

1 Answers

4
votes

Array is a profunctor from the category of index-remapping functions into the normal Hask category (unconstrained Haskell types with Haskell functions as morphisms).

There is a fairly widespread class for profunctors HaskHask, but it has no way to express the Ix constraint. That could easily be expressed in the constrained-categories framework though:

class (Category r, Category t) => Profunctor p r t where
  dimap :: (Object r a, Object r b, Object t c, Object t d)
     => r a b -> t c d -> p b c -> p a d

Now, to actually use this with Array, we need to lift the ranges of allowed indices into the type level. I.e. instead of using Int as the index type – which is kind of unsafe, because it allows indexing outside the range... we clearly can't have that in a category theory setting! – we use only a type that has the allowed range baked in. Rather than actually hacking this into Array, let me use Vector (which doesn't bother offering different index types at all) as the low-level representation:

{-# LANGUAGE DataKinds, TypeFamilies, AllowAmbiguousTypes, TypeApplications, ScopedTypeVariables, UnicodeSyntax #-}

import GHC.TypeLits (Nat, natVal)
import Data.Vector (Vector)
import qualified Data.Vector as V

newtype Range (lb :: Nat) (ub :: Nat)
     = Range { getIndexInRange :: Int -- from 0 to ub-lb-1
             }

newtype SafeArray i a = SafeArray {
    getFlattenedArray :: Vector a  -- length must equal `rangeLength @i`
  }

class ToLinearIndex r where
  rangeLength :: Int
  toLinearIndex :: r -> Int

instance ∀ lb ub . ToLinearIndex (Range lb ub) where
  rangeLength = fromInteger $ natVal @rb [] - natVal @lb []
  toLinearIndex = getIndexInRange
instance ∀ rx ry . (ToLinearIndex rx, ToLinearIndex ry)
     => ToLinearIndex (rx, ry) where
  rangeLength = rangeLength @rx * rangeLength @ry
  toLinearIndex (ix, iy)
      = toLinearIndex ix + rangeLength @rx * toLinearIndex iy

(!) :: ToLinearIndex i => SafeArray i a -> i -> a
SafeArray v ! i = V.unsafeIndex v $ toLinearIndex i

newtype IxMapFn r s = IxMapFn {
   getIxMapFn :: Int -> Int  -- input and output must be <rangeLength
                             -- of `r` and `s`, respectively
  }

instance Category IxMapFn where
  type Object IxMapFn i = ToLinearIndex i
  id = IxMapFn id
  IxMapFn f . IxMapFn g = IxMapFn $ f . g

saDiMap :: ∀ r s a b . (ToLinearIndex r, ToLinearIndex s)
      => IxMapFn s r -> (a -> b) -> SafeArray r a -> SafeArray s b
saDiMap (IxMapFn f) g (SafeArray v)
    = SafeArray . V.generate (rangeLength @s)
       $ g . V.unsafeIndex v . f

instance Profunctor SafeArray IxMapFn (->) where
  dimap = saDimMap

I've never gotten around to adding a profunctor class to constrained-categories, mostly because I think profunctors are a bit of an abused abstraction in Haskell: often when people use endo-profunctors, what they actually mean to express is simply a category / Arrow.