| Portability | non-portable | 
|---|---|
| Stability | experimental | 
| Maintainer | vector-th-unbox@liyang.hu | 
| Safe Haskell | None | 
Data.Vector.Unboxed.Deriving
Description
Writing Unbox instances for new data types is tedious and formulaic. More
often than not, there is a straightforward mapping of the new type onto some
existing one already imbued with an Unbox instance. The example from the
vector package represents Complex a as pairs (a, a). (See
http://hackage.haskell.org/packages/archive/vector/latest/doc/html/Data-Vector-Unboxed.html.)
Using derivingUnbox, we can define the same instances much more
succinctly:
derivingUnbox "Complex"
    [d| instance (Unbox a) => Unbox' (Complex a) (a, a) |]
    [| \ (r :+ i) -> (r, i) |]
    [| \ (r, i) -> r :+ i |]
Requires the MultiParamTypeClasses, TemplateHaskell and TypeFamilies
LANGUAGE extensions.
The dummy Unbox' class provides a convenient way to pass in the source
and representation types, along with any requisite constraints.
Documentation
A dummy class for passing arguments to derivingUnbox.
Arguments
| :: String | Unique constructor suffix for the MVector and Vector data families | 
| -> DecsQ | Quotation of the form  | 
| -> ExpQ | Quotation of an expression of type  | 
| -> ExpQ | Quotation of an expression of type  | 
| -> DecsQ | Declarations to be spliced for the derived Unbox instance | 
Let's consider a more complex example: suppose we want an Unbox
instance for Maybe a. We can encode this using the pair (Bool, a), with
the boolean indicating whether we have Nothing or Just something. This
encoding requires a dummy value in the Nothing case, necessitating an
additional Default (see the data-default package) constraint. Thus:
derivingUnbox "Maybe"
    [d| instance (Default a, Unbox a) => Unbox' (Maybe a) (Bool, a) |]
    [| maybe (False, def) (\ x -> (True, x)) |]
    [| \ (b, x) -> if b then Just x else Nothing |]