I also want to automatically derive instances of this class for other types using the Generic typeclass. Ideally these instances would be the most efficient possible, so that for example the instance for (Int, Int) used two unboxed arrays but the instance for Maybe Int uses a boxed array. To that end I created another typeclass and wrote instances for the Generic data constructors:
class VectorElementG (r :: * -> *) where
data VectorG r
replicateG :: Int -> r a -> VectorG r
lengthG :: VectorG r -> Int
instance VectorElementG V1 where
data VectorG V1
replicateG = undefined
lengthG = undefined
instance VectorElementG U1 where
newtype VectorG U1 = VectorGUnit Int
replicateG i U1 = VectorGUnit i
lengthG (VectorGUnit i) = i
instance VectorElement a => VectorElementG (K1 i a) where
newtype VectorG (K1 i a) = VectorGK (Vector a)
replicateG i (K1 x) = VectorGK $ replicate i x
lengthG (VectorGK v) = length v
instance (VectorElementG r1, VectorElementG r2) => VectorElementG (r1 :*: r2) where
data VectorG (r1 :*: r2) = VectorGProd (VectorG r1) (VectorG r2)
replicateG i (a :*: b) = VectorGProd (replicateG i a) (replicateG i b)
lengthG (VectorGProd v _) = lengthG v
instance VectorElement ((r1 :+: r2) p) where
newtype Vector ((r1 :+: r2) p) = VectorSum (V.Vector ((r1 :+: r2) p))
replicate i x = VectorSum $ V.replicate i x
length (VectorSum v) = V.length v
instance VectorElementG f => VectorElementG (M1 i c f) where
newtype VectorG (M1 i c f) = VectorGMeta (VectorG f)
replicateG i (M1 f) = VectorGMeta $ replicateG i f
lengthG (VectorGMeta v) = lengthG v
I’m not sure if these are correct, especially the one for :+:. I want basically base cases to be any type that already has an instance of VectorElement or a sum type which is automatically boxed, and the recursive case to basically just use parallel vectors for product types.