Unboxed Vectors of newtype'd values
Andres Löh
andres at well-typed.com
Tue Jun 5 21:54:05 CEST 2012
Hi Bryan.
> Yes, I (and I assume Bas) want generalised newtype deriving to work, but it
> doesn't.
>
> I want to write something very simple:
>
> {-# LANGUAGE GeneralizedNewtypeDeriving #-}
> newtype Foo = Foo Int
> deriving (Eq, Show, Unbox)
>
> But with the above, GHC says:
>
> No instances for (M.MVector MVector Foo, G.Vector Vector Foo)
> arising from the 'deriving' clause of a data type declaration
Yes, because these are superclasses of Unbox. So can't you simply say this:
> newtype Foo = Foo Int
> deriving (Eq, Show, Unbox, M.MVector MVector, G.Vector Vector)
?
Cheers,
Andres
--
Andres Löh, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com
More information about the Libraries
mailing list