
On 2 January 2015 at 07:02, Michael Orlitzky
I've been playing with generic conversions between simple product types. For example, converting (Bar Int Int) back and forth between (Int,Int). See,
https://www.haskell.org/pipermail/haskell-cafe/2014-December/117489.html
These save me a *lot* of boilerplate. But naturally, I've gotten greedy. Another transformation I need to make takes one data type, and sticks a new field on the beginning of it. So I'd like to be able to take a,
Foo Int Int
and construct a,
BigFoo String Int Int
with as little code as possible. In my real problem, Foo may have 30 fields, and BigFoo 31 -- if you know of a better way, stop me now.
Please stop. Some time ago I wrote library exactly for working with product types: fixed-vector-hetero. Example code below. I think
{-# LANGUAGE DeriveGeneric #-} import qualified Data.Vector.HFixed as H import GHC.Generics (Generic)
data Foo = Foo Int Int deriving (Show,Generic) data BigFoo = BigFoo String Int Int deriving (Show,Generic)
-- Instances are generated automatically using Generic. It's of course -- possible to write them manually instance H.HVector Foo instance H.HVector BigFoo
Now you can convert tuple to bar (or any other product types which have same elemets) *Main> H.convert (12,12) :: Foo Foo 12 12 *Main> H.cons "A" (Foo 1 2) :: BigFoo BigFoo "A" 1 2 Note. I've never tuned it for performance.