Hello,

I am working on a Vector class, heavily based on the paper "Faking It: Simulating Dependent Types in Haskell" by Connor McBride.

Here is a stripped down version of my code:

---

{-# LANGUAGE RankNTypes #-}
                           
import Control.Applicative
import Data.Functor

infixr 5 :.
data Cons u t = (:.) t (u t) deriving (Show)

data Nil t = Nil deriving (Show)

class (Applicative v, Functor v) => Vector v where
  wrap :: (forall u. Vector u => s -> f (u t) -> f (Cons u t)) -> f (Nil t) -> v s -> f (v t)

instance (Vector u) => Vector (Cons u) where
  wrap f n (x:.xs) = f x (wrap f n xs)

instance Vector Nil where
  wrap _ n Nil = n

instance (Applicative u) => Applicative (Cons u) where
  pure x = x:.(pure x)
  (f:.fs) <*> (x:.xs) = (f x):.(fs <*> xs)

instance Applicative Nil where
  pure _ = Nil
  _ <*> _ = Nil

instance (Functor u) => Functor (Cons u) where
  fmap f (x:.xs) = (f x):.(fmap f xs)

instance Functor Nil where
  fmap _ Nil = Nil

transpose :: (Vector w, Vector u) => w (u t) -> u (w t)
transpose v = wrap (\x xs -> (:.) <$> x <*> xs) (pure Nil) v

---

I am having trouble understanding the type signature of 'wrap'. This is how I interpret it:
(function that takes an 's' and container of 'u t' and returns a container of 'Cons u t') -> 
(container of 'Nil') -> 
(a vector of 's') -> 
(a container with the same type as the container of Nil, but containing v t instead)

What doesn't make sense to me is how the signature seems to imply that the structure of the container in the return type is the same as the structure of the container holding the Nils, but in 'transpose' the container holding Nil seems to be infinite.

Can someone help me to understand what is going on here?

Thanks,
Ben