On Thursday 08 December 2011, 21:55:46, Paul Monday wrote:
data UMatrix a = UMatrix (V.Vector (U.Vector a))
deriving (Show, Eq)
madd3 :: (U.Unbox a, Num a) => UMatrix a -> UMatrix a -> UMatrix a
madd3 (UMatrix m) (UMatrix n) = UMatrix $ V.zipWith (U.zipWith (+)) m n
And it works … (really, when I started writing this note, I was
completely lost … welcome to the power of sitting and walking through
Haskell)
madd3 (UMatrix (Data.Vector.fromList [Data.Vector.Unboxed.fromList
[1,2,3], Data.Vector.Unboxed.fromList [4,5,6],
Data.Vector.Unboxed.fromList [7,8,9]])) (UMatrix (Data.Vector.fromList
[Data.Vector.Unboxed.fromList [10,11,12], Data.Vector.Unboxed.fromList
[13,14,5], Data.Vector.Unboxed.fromList [16,17,18]]))
I have ONE thing that I can't really explain …
Why does the declaration of madd3 REQUIRE the use of U.Unbox a as a data
type? madd3 :: (U.Unbox a, Num a) => UMatrix a -> UMatrix a -> UMatrix
a
I would have thought that my declaration of UMatrix would have done
this?
No, the data declaration doesn't provide any such context, hence you have
to specify it at the use site (I don't think for types which aren't
instances of Unbox there are any values other than _|_, though).
You can make the Unbox constraint available from the data declaration if
you use GADTs,
{-# LANGUAGE GADTs #-}
data UMatrix e where
UMatrix :: U.Unbox a => V.Vector (U.Vector a) -> UMatrix a
Then pattern-matching on a UMatrix makes the Unbox dictionary of a
available.