Unboxed Vectors of newtype'd values

One of the reasons I find Haskell so well suited to my work is its ability to easily work with large quantities of data. In particular, I find myself using Data.Vector.Unbox quite frequently. Another of my reasons for using Haskell is the type safety it provides. I find myself using newtypes very frequently to force myself to think about invariants that a more weakly typed language would allow me to simply ignore. Sadly, these two features don't interact particularly well. While the Data.Vector.Unbox documentation claims that "Implementing unboxed vectors for new data types can be very easy", it then goes on to list an abridged version of the Complex instance---dozens of lines of code. While this code certainly isn't difficult to write, it is time consuming, error-prone, and, above else, utterly mind deadeningly dull (making it quite uncharacteristic for Haskell). So dull that I generally avoid newtypes at all cost in code that might need to use unboxed vectors. This boilerplate is largely due to Vector's use of type families as this precludes the use of (the otherwise quite cunning) GeneralizedNewtypeDeriving to automatically derive the necessary instances. What can be done to fix this unfortunate state of affairs? The obvious solution here seems to be Template Haskell, but this seems a bit of an unfortunate hack around what might be a deficiency in the type families mechanism (or at least this application of it). The newtype package provides a nice mechanism to pack and unpack newtypes, but providing blanket Unbox instances for Newtype instances seems like an awful idea (and, frankly, I'm not sure how this would work with type families). Other than these two possibilities I am at a loss. Thoughts? I'd appreciate any ideas folks could offer. Cheers, - Ben

I don't have a proposal, but I'd like to echo my support for thinking about
this problem. It is very annoying to use my own types with unboxed vectors.
On May 30, 2012 12:28 AM, "Ben Gamari"
One of the reasons I find Haskell so well suited to my work is its ability to easily work with large quantities of data. In particular, I find myself using Data.Vector.Unbox quite frequently.
Another of my reasons for using Haskell is the type safety it provides. I find myself using newtypes very frequently to force myself to think about invariants that a more weakly typed language would allow me to simply ignore.
Sadly, these two features don't interact particularly well. While the Data.Vector.Unbox documentation claims that "Implementing unboxed vectors for new data types can be very easy", it then goes on to list an abridged version of the Complex instance---dozens of lines of code. While this code certainly isn't difficult to write, it is time consuming, error-prone, and, above else, utterly mind deadeningly dull (making it quite uncharacteristic for Haskell). So dull that I generally avoid newtypes at all cost in code that might need to use unboxed vectors. This boilerplate is largely due to Vector's use of type families as this precludes the use of (the otherwise quite cunning) GeneralizedNewtypeDeriving to automatically derive the necessary instances.
What can be done to fix this unfortunate state of affairs? The obvious solution here seems to be Template Haskell, but this seems a bit of an unfortunate hack around what might be a deficiency in the type families mechanism (or at least this application of it). The newtype package provides a nice mechanism to pack and unpack newtypes, but providing blanket Unbox instances for Newtype instances seems like an awful idea (and, frankly, I'm not sure how this would work with type families). Other than these two possibilities I am at a loss. Thoughts? I'd appreciate any ideas folks could offer.
Cheers,
- Ben
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Wed, May 30, 2012 at 9:50 AM, Bryan O'Sullivan
Likewise, if anyone is listening :-)
Here too. I'd like some compiler support for abstracting over unboxed values in general and e.g. generate Unbox instances automatically. Then we could have other unboxed structures than Vector.

| I'd like some compiler support for abstracting over unboxed values in
| general and e.g. generate Unbox instances automatically. Then we could
| have other unboxed structures than Vector.
Could someone post an example or two of the problem being described here?
Simon
| -----Original Message-----
| From: libraries-bounces@haskell.org [mailto:libraries-
| bounces@haskell.org] On Behalf Of Johan Tibell
| Sent: 30 May 2012 17:57
| To: Bryan O'Sullivan
| Cc: Jake McArthur; libraries@haskell.org
| Subject: Re: Unboxed Vectors of newtype'd values
|
| On Wed, May 30, 2012 at 9:50 AM, Bryan O'Sullivan

On 4 June 2012 12:43, Simon Peyton-Jones
| I'd like some compiler support for abstracting over unboxed values in | general and e.g. generate Unbox instances automatically. Then we could | have other unboxed structures than Vector.
Could someone post an example or two of the problem being described here?
The following is some boring code I wrote a while back at work for storing UUIDs[1] in unboxed vectors: {-# LANGUAGE MultiParamTypeClasses, TypeFamilies #-} import Control.Monad (liftM) import Data.Word (Word32) import Data.UUID (UUID) import qualified Data.UUID as UUID import qualified Data.Vector.Unboxed as VU import qualified Data.Vector.Generic as VG import qualified Data.Vector.Generic.Mutable as VGM newtype instance VU.MVector s UUID = MV_UUID (VU.MVector s (Word32, Word32, Word32, Word32)) newtype instance VU.Vector UUID = V_UUID (VU.Vector (Word32, Word32, Word32, Word32)) instance VU.Unbox UUID instance VGM.MVector VU.MVector UUID where {-# INLINE basicLength #-} {-# INLINE basicUnsafeSlice #-} {-# INLINE basicOverlaps #-} {-# INLINE basicUnsafeNew #-} {-# INLINE basicUnsafeReplicate #-} {-# INLINE basicUnsafeRead #-} {-# INLINE basicUnsafeWrite #-} {-# INLINE basicClear #-} {-# INLINE basicSet #-} {-# INLINE basicUnsafeCopy #-} {-# INLINE basicUnsafeGrow #-} basicLength (MV_UUID v) = VGM.basicLength v basicUnsafeSlice i n (MV_UUID v) = MV_UUID $ VGM.basicUnsafeSlice i n v basicOverlaps (MV_UUID v1) (MV_UUID v2) = VGM.basicOverlaps v1 v2 basicUnsafeNew n = MV_UUID `liftM` VGM.basicUnsafeNew n basicUnsafeReplicate n uuid = MV_UUID `liftM` VGM.basicUnsafeReplicate n (UUID.toWords uuid) basicUnsafeRead (MV_UUID v) i = fromQuadruple `liftM` VGM.basicUnsafeRead v i basicUnsafeWrite (MV_UUID v) i uuid = VGM.basicUnsafeWrite v i (UUID.toWords uuid) basicClear (MV_UUID v) = VGM.basicClear v basicSet (MV_UUID v) uuid = VGM.basicSet v (UUID.toWords uuid) basicUnsafeCopy (MV_UUID v1) (MV_UUID v2) = VGM.basicUnsafeCopy v1 v2 basicUnsafeMove (MV_UUID v1) (MV_UUID v2) = VGM.basicUnsafeMove v1 v2 basicUnsafeGrow (MV_UUID v) n = MV_UUID `liftM` VGM.basicUnsafeGrow v n instance VG.Vector VU.Vector UUID where {-# INLINE basicUnsafeFreeze #-} {-# INLINE basicUnsafeThaw #-} {-# INLINE basicLength #-} {-# INLINE basicUnsafeSlice #-} {-# INLINE basicUnsafeIndexM #-} {-# INLINE elemseq #-} basicUnsafeFreeze (MV_UUID v) = V_UUID `liftM` VG.basicUnsafeFreeze v basicUnsafeThaw (V_UUID v) = MV_UUID `liftM` VG.basicUnsafeThaw v basicLength (V_UUID v) = VG.basicLength v basicUnsafeSlice i n (V_UUID v) = V_UUID $ VG.basicUnsafeSlice i n v basicUnsafeIndexM (V_UUID v) i = fromQuadruple `liftM` VG.basicUnsafeIndexM v i basicUnsafeCopy (MV_UUID mv) (V_UUID v) = VG.basicUnsafeCopy mv v elemseq _ uuid z = VG.elemseq (undefined :: VU.Vector a) a $ VG.elemseq (undefined :: VU.Vector a) b $ VG.elemseq (undefined :: VU.Vector a) c $ VG.elemseq (undefined :: VU.Vector a) d z where (a,b,c,d) = UUID.toWords uuid fromQuadruple :: (Word32, Word32, Word32, Word32) -> UUID fromQuadruple (a,b,c,d) = UUID.fromWords a b c d Regards, Bas [1] http://hackage.haskell.org/packages/archive/uuid/1.2.5/doc/html/Data-UUID.ht...

My desire probably doesn't overlap much with what others have described in this thread, apologies. I *think* they want generalized newtype deriving to work for Unbox instances. I want to be able to write definition like this (pseudo code): data UnpackedList a = forall a. Unbox a => Cons {-# UNPACK #-} !a (UnpackedList a) | Nil and have GHC generate appropriate data type definitions at call sites. In other words, I want polymorphic unpacking to work as long as the unpacked field is unboxable (i.e. is member of some Unobx type class.) I believe I've described this desire to you before. Unfortunately it seems like a really hard problem. -- Johan

I'm sorry I'm still struggling. In your example below you bind 'a' twice, once with the "data UnpackedList a" and once with the "forall a". Did you intend an existential? Also I don't know what you mean by "generate appropriate type definitions at call sites". I do remember a dinner conversation in Tokyo where I couldn't figure out how to implement what you wanted, but I've forgotten the details. Maybe it's worth a wiki page to explain -- or maybe not if its un-implementable. Anyway thanks for distinguishing the two threads. If you can clarify the generalised newtype deriving problem too that would be great. Simon | -----Original Message----- | From: Johan Tibell [mailto:johan.tibell@gmail.com] | Sent: 04 June 2012 20:58 | To: Bas van Dijk | Cc: Simon Peyton-Jones; Bryan O'Sullivan; Jake McArthur; | libraries@haskell.org | Subject: Re: Unboxed Vectors of newtype'd values | | My desire probably doesn't overlap much with what others have described | in this thread, apologies. I *think* they want generalized newtype | deriving to work for Unbox instances. | | I want to be able to write definition like this (pseudo code): | | data UnpackedList a = forall a. Unbox a => Cons {-# UNPACK #-} !a | (UnpackedList a) | Nil | | and have GHC generate appropriate data type definitions at call sites. | In other words, I want polymorphic unpacking to work as long as the | unpacked field is unboxable (i.e. is member of some Unobx type class.) | | I believe I've described this desire to you before. Unfortunately it | seems like a really hard problem. | | -- Johan

On Tue, Jun 5, 2012 at 12:06 AM, Simon Peyton-Jones
I'm sorry I'm still struggling. In your example below you bind 'a' twice, once with the "data UnpackedList a" and once with the "forall a". Did you intend an existential?
I didn't intend the existential. I haven't made any real progress on my unpacking problem since we last talked so lets let it rest for now. I'll try to find some time to write down a wiki page so we at least know where we got stuck last time. Perhaps someone reading it will have an aha moment that will let us move forward.
Also I don't know what you mean by "generate appropriate type definitions at call sites".
If I write: module A data UnpackedList a = Unbox a => Cons {-# UNPACK #-} !a (UnpackedList a) | Nil { -# INLINABLE_DATA UnpackedList #-} -- Like INLINABLE, but for data types module B f :: UnpackedList Int -> ... I'd like GHC to generate data UnpackedListInt = ConsInt {-# UNPACK #-} !Int UnpackedListInt | NilInt and a specialized version of f, using that type, in B. It's a bit like the call-site specialization afforded by the INLINABLE pragma, but applied also to data type definitions. You might protest and say that I could just just use type families, but they don't work well if my type has more than one type parameter (e.g. Map), as I need to write O(n^2) instances: instance Map Int Int where type Map = MapIntInt ...{-# UNPACK #-} !Int {-# UNPACK #-} !Int... instance Map Int Char where type Map = MapIntChar ... instance Map Int (Int, Int) where type Map = MapIntIntInt ... That's 50,625 instances to just cover the basic types (e.g. Int, Word, etc) and pairs. The reason you'd want call-site generation of data types (ala C++ templates) is that a real program would only use no more than 100 (for a big program) of the potentially infinite number of combinations.
Anyway thanks for distinguishing the two threads. If you can clarify the generalised newtype deriving problem too that would be great.
I'll leave it to others. I'm not quite sure what the issue is. -- Johan

I see the boring code, but I don't see what you *want*! I'm guessing you want "generalised newtype deriving" but why does that not work?
S
| -----Original Message-----
| From: Bas van Dijk [mailto:v.dijk.bas@gmail.com]
| Sent: 04 June 2012 20:41
| To: Simon Peyton-Jones
| Cc: Johan Tibell; Bryan O'Sullivan; Jake McArthur; libraries@haskell.org
| Subject: Re: Unboxed Vectors of newtype'd values
|
| On 4 June 2012 12:43, Simon Peyton-Jones

On Tue, Jun 5, 2012 at 12:02 AM, Simon Peyton-Jones
I see the boring code, but I don't see what you *want*! I'm guessing you want "generalised newtype deriving" but why does that not work?
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 And then we begin the journey that eventually gets us to Bas's rather wordy code.

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

Yep, that works! Sweet!
On Tue, Jun 5, 2012 at 3:54 PM, Andres Löh
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
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Andres Löh
Hi Bryan.
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)
Wonderful! I suppose that should have been clear from the error. Thanks! Cheers, - Ben

Andres Löh wrote:
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)
I don't think this should work. This is the basic set up: class G.Vector v a where basicLength :: v a -> Int ... data family Vector a newtype instance Vector Int = V_Int ... instance G.Vector Vector Int where basicLength (V_Int ...) = ... ... I don't understand what GeneralizedNewtypeDeriving does with deriving(G.Vector Vector) in this situation but it can't possibly do anything sensible without a data instance Vector Foo. The fact that it doesn't fail is just a bug, IMO. Roman

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)
I don't think this should work. This is the basic set up:
[...]
I don't understand what GeneralizedNewtypeDeriving does with deriving(G.Vector Vector) in this situation but it can't possibly do anything sensible without a data instance Vector Foo. The fact that it doesn't fail is just a bug, IMO.
I've actually started wondering the same after I posted this. I tried to use -ddump-deriv to get at the code, but GHC seems to be cheating and doesn't show what it generates. I guess I understand newtype-deriving less than I thought ... Cheers, Andres -- Andres Löh, Haskell Consultant Well-Typed LLP, http://www.well-typed.com

Andres Löh wrote:
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)
I don't think this should work. This is the basic set up:
[...]
I don't understand what GeneralizedNewtypeDeriving does with deriving(G.Vector Vector) in this situation but it can't possibly do anything sensible without a data instance Vector Foo. The fact that it doesn't fail is just a bug, IMO.
I've actually started wondering the same after I posted this. I tried to use -ddump-deriv to get at the code, but GHC seems to be cheating and doesn't show what it generates. I guess I understand newtype-deriving less than I thought ...
I don't really understand it, either, and try to stay well away from it :-) It simply doesn't seem to work with GADTs, type families etc. I've created a ticket: http://hackage.haskell.org/trac/ghc/ticket/6147. Roman

So Andres has explained how to do what Johan asks. Does that mean that Bas’s problem is solved?
S
From: Bryan O'Sullivan [mailto:bos@serpentine.com]
Sent: 05 June 2012 18:57
To: Simon Peyton-Jones
Cc: Bas van Dijk; Johan Tibell; Jake McArthur; libraries@haskell.org
Subject: Re: Unboxed Vectors of newtype'd values
On Tue, Jun 5, 2012 at 12:02 AM, Simon Peyton-Jones

On Tue, Jun 5, 2012 at 1:46 PM, Bryan O'Sullivan
I think so - thanks, Andres! I believe that Johan's problem is another beast entirely.
Just to make it clear why I butted into this thread to begin with (apologies for that.) I also want a deriving Unbox mechanism, but with a more magic Unbox class (e.g. one that knew enough about the representation of a data type to unpack it.) That was the connection. -- Johan

On 5 June 2012 22:45, Simon Peyton-Jones
So Andres has explained how to do what Johan asks. Does that mean that Bas’s problem is solved?
My problem can't be solved with GeneralizedNewtypeDeriving since a UUID is not a newtype but an abstract data type defined in another package[1]. However, the template-haskell from the vector-th-unbox package which Reiner mentioned does the job perfectly: derivingUnbox "UUID" [d| instance Unbox' UUID (Word32, Word32, Word32, Word32) |] [| \ uuid -> UUID.toWords uuid|] [| \ (a,b,c,d) -> UUID.fromWords a b c d |] Thanks Reiner for pointing me to this package! Cheers, Bas [1] http://hackage.haskell.org/packages/archive/uuid/latest/doc/html/src/Data-UU...

| > So Andres has explained how to do what Johan asks. Does that mean | > that Bas’s problem is solved? | | My problem can't be solved with GeneralizedNewtypeDeriving since a UUID | is not a newtype but an abstract data type defined in another | package[1]. | | However, the template-haskell from the vector-th-unbox package which | Reiner mentioned does the job perfectly: | | derivingUnbox "UUID" | [d| instance Unbox' UUID (Word32, Word32, Word32, Word32) |] | [| \ uuid -> UUID.toWords uuid|] | [| \ (a,b,c,d) -> UUID.fromWords a b c d |] Ah, well, that is another matter. GeneralisedNewtypeDeriving respects the abstraction boundaries imposed by the package author. I think Template Haskell does not. It probably should; see [1]. So it seems that * generalised newtype deriving will do your job, if you can persuade the package author to expose the representation * Template Haskell can do the job, but only because of a bug (arguably) So this is really a library design question, not a language design one. If a package author makes a type abstract, he's saying that he does not want you to look at the representation; and yet you must if you want to unbox it. So you must negotiate with the package author. I don't see how the language can (a) respect abstractions and (b) let you retrospectively unbox abstract types. [1] http://stackoverflow.com/questions/10857030/whats-so-bad-about-template-hask...

On 6 June 2012 09:59, Simon Peyton-Jones
* generalised newtype deriving will do your job, if you can persuade the package author to expose the representation
Just exposing the representation is not enough to get GeneralizedNewtypeDeriving to work since UUIDs are not newtypes but datatypes. The only way to get it to work is to persuade the author to expose the representation _and_ turn it into a newtype. But a newtype of what? newtype UUID = UUID (Word32,Word32,Word32,Word32) is not better than the current fully unboxed representation.
* Template Haskell can do the job, but only because of a bug (arguably)
I don't think vector-th-unbox is exploiting a bug. It doesn't need to inspect the private representation of a UUID. The only thing that it needs is a type that is isomorphic to a UUID and conversion functions between them.
So this is really a library design question, not a language design one. If a package author makes a type abstract, he's saying that he does not want you to look at the representation; and yet you must if you want to unbox it. So you must negotiate with the package author. I don't see how the language can (a) respect abstractions and (b) let you retrospectively unbox abstract types.
Agreed. Regards, Bas

On 30/05/2012, at 05:27, Ben Gamari wrote:
Sadly, these two features don't interact particularly well. While the Data.Vector.Unbox documentation claims that "Implementing unboxed vectors for new data types can be very easy", it then goes on to list an abridged version of the Complex instance---dozens of lines of code. While this code certainly isn't difficult to write, it is time consuming, error-prone, and, above else, utterly mind deadeningly dull (making it quite uncharacteristic for Haskell). So dull that I generally avoid newtypes at all cost in code that might need to use unboxed vectors. This boilerplate is largely due to Vector's use of type families as this precludes the use of (the otherwise quite cunning) GeneralizedNewtypeDeriving to automatically derive the necessary instances.
I completely agree that the current situation is less than ideal but don't really have a good solution. Frankly, the easiest way of defining Unbox instances for newtypes is probably a preprocessor macro. I use a lot of those in vector to reduce boilerplate and they work well. I'll provide one for newtypes in the next release. As you say, TH is another possibility but one I'm rather wary of. Roman

It seems like the most elegant long-term solution here is to make
GeneralizedNewtypeDeriving more cunning. Is there some fundamental reason
it can't work with the type families involved?
But in the short term, I agree and TH is probably best.
-Dan
On Wed, May 30, 2012 at 3:41 PM, Roman Leshchinskiy
On 30/05/2012, at 05:27, Ben Gamari wrote:
Sadly, these two features don't interact particularly well. While the Data.Vector.Unbox documentation claims that "Implementing unboxed vectors for new data types can be very easy", it then goes on to list an abridged version of the Complex instance---dozens of lines of code. While this code certainly isn't difficult to write, it is time consuming, error-prone, and, above else, utterly mind deadeningly dull (making it quite uncharacteristic for Haskell). So dull that I generally avoid newtypes at all cost in code that might need to use unboxed vectors. This boilerplate is largely due to Vector's use of type families as this precludes the use of (the otherwise quite cunning) GeneralizedNewtypeDeriving to automatically derive the necessary instances.
I completely agree that the current situation is less than ideal but don't really have a good solution. Frankly, the easiest way of defining Unbox instances for newtypes is probably a preprocessor macro. I use a lot of those in vector to reduce boilerplate and they work well. I'll provide one for newtypes in the next release.
As you say, TH is another possibility but one I'm rather wary of.
Roman
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

In case anyone missed it, Liyang HU wrote a TH deriver for Unbox
instances[1].
Also, I have tried using GHC's new generic deriving[2] to derive instances
- this is almost possible, but is blocked by a GHC issue[3]. IMHO generic
deriving would be the best solution (once it works), because it works for
product types as well as newtypes, and requires no extra GHC assistance or
TH.
[1]
http://hackage.haskell.org/packages/archive/vector-th-unbox/0.1.0.0/doc/html...
[2]
http://www.haskell.org/ghc/docs/7.4.1/html/users_guide/generic-programming.h...
[3] http://hackage.haskell.org/trac/ghc/ticket/5936
Cheers,
Reiner
On 30 May 2012 22:03, Daniel Peebles
It seems like the most elegant long-term solution here is to make GeneralizedNewtypeDeriving more cunning. Is there some fundamental reason it can't work with the type families involved?
But in the short term, I agree and TH is probably best.
-Dan
On Wed, May 30, 2012 at 3:41 PM, Roman Leshchinskiy
wrote: On 30/05/2012, at 05:27, Ben Gamari wrote:
Sadly, these two features don't interact particularly well. While the Data.Vector.Unbox documentation claims that "Implementing unboxed vectors for new data types can be very easy", it then goes on to list an abridged version of the Complex instance---dozens of lines of code. While this code certainly isn't difficult to write, it is time consuming, error-prone, and, above else, utterly mind deadeningly dull (making it quite uncharacteristic for Haskell). So dull that I generally avoid newtypes at all cost in code that might need to use unboxed vectors. This boilerplate is largely due to Vector's use of type families as this precludes the use of (the otherwise quite cunning) GeneralizedNewtypeDeriving to automatically derive the necessary instances.
I completely agree that the current situation is less than ideal but don't really have a good solution. Frankly, the easiest way of defining Unbox instances for newtypes is probably a preprocessor macro. I use a lot of those in vector to reduce boilerplate and they work well. I'll provide one for newtypes in the next release.
As you say, TH is another possibility but one I'm rather wary of.
Roman
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Reiner Pope
In case anyone missed it, Liyang HU wrote a TH deriver for Unbox instances[1].
Thanks! I don't know how I missed this. This is quite sufficient for most of my purposes.
Also, I have tried using GHC's new generic deriving[2] to derive instances - this is almost possible, but is blocked by a GHC issue[3]. IMHO generic deriving would be the best solution (once it works), because it works for product types as well as newtypes, and requires no extra GHC assistance or TH.
This will be quite nice and it sounds like it should cover nearly all of the cases I'm interested in. I'm not terribly familiar with generics support so I'm not sure whether this is possible or not, but it would be great if there were a way to specify whether an SoA or AoS representation is derived. This way one could write nearly cache-optimal code while keeping the mechanics of data layout nicely contained. Cheers, - Ben
participants (10)
-
Andres Löh
-
Bas van Dijk
-
Ben Gamari
-
Bryan O'Sullivan
-
Daniel Peebles
-
Jake McArthur
-
Johan Tibell
-
Reiner Pope
-
Roman Leshchinskiy
-
Simon Peyton-Jones