
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. And, I actually managed to do it using generics-sop:
prepend "Hello" (Foo 1 2) :: BigFoo BigFoo "Hello" 1 2
But, I had to do something dirty; I used an incomplete pattern match. I don't know enough about what's going on here to handle the other case for prepend_sop. I basically guessed the existing type signatures because it wouldn't work without them. I would like to either, a) Get prepend_sop working for sums of products (the missing case), not just a single product (the one I've got working) b) Restrict prepend_sop to the case that I've got working via the type system, somehow In other words, I don't want it to be crashy, but I'm stuck. Here's the complete working code for the example above. {-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} module Prepend where import qualified GHC.Generics as GHC import Generics.SOP data Foo = Foo Int Int deriving (Show, GHC.Generic) instance Generic Foo -- A "copy" of Foo, with a String in front of it. data BigFoo = BigFoo String Int Int deriving (Show, GHC.Generic) instance Generic BigFoo prepend_sop :: (xss ~ (x ': xs), (yss ~ ((a ': x) ': xs))) => a -> SOP I xss -> SOP I yss prepend_sop z (SOP (Z rest)) = SOP $ Z ((I z) :* rest) --prepend_sop z (SOP (S rest)) = ??? prepend :: (Generic a, Generic c, Code a ~ (x ': xs), Code c ~ ((b ': x) ': xs)) => b -> a -> c prepend z = to . (prepend_sop z) . from