Modifying a product type generically

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

The absent case corresponds to a multi-constructor type. You need to decide what to do in that case. You can decide not to allow it, in which case you can enforce it by saying (xss ~ '[x], yss ~ '[a ': x]) (essentially replacing xs with '[]). Or perhaps you do want to handle those cases; then it depends on how exactly you want to map multiple constructors. Roman On 02/01/15 06:02, Michael Orlitzky wrote:
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 _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 01/02/2015 04:22 AM, Roman Cheplyaka wrote:
The absent case corresponds to a multi-constructor type. You need to decide what to do in that case.
You can decide not to allow it, in which case you can enforce it by saying
(xss ~ '[x], yss ~ '[a ': x])
(essentially replacing xs with '[]).
Or perhaps you do want to handle those cases; then it depends on how exactly you want to map multiple constructors.
Thanks, this is so cool. Like, I'm eight years old with a working machine gun cool. First, I got it working with your type signature above. That really helped me understand what was going on, but GHC still warned me about the missing case, and I didn't want to "error" it. I see now that `xss` and `yss` are type-level lists-of-lists, and that there's more than one element in that list if we have more than one constructor. If I want to prepend a new type to the list for both cases, I need something better than [a ': x], which only appends the type `a` to the FIRST (only) list in the list-of-lists. Unfortunately, there are no sections for type operators yet =) So this doesn't work: Map (a ':) xs. But the following recursive definition does: type family Prepended a (xs :: [k]) :: [l] type instance Prepended a '[] = '[] type instance Prepended a (x ': xs) = (a ': x) ': (Prepended a xs) The dubious second line makes sense when you realize that we're working on lists-of-lists, and prepending to the INNER lists. Now the type of `yss` is obvious. In fact, we don't need `yss` any more: prepend_sop :: a -> SOP I xss -> SOP I (Prepended a xss) The first case is the same: prepend_sop z (SOP (Z rest)) = SOP $ Z ((I z) :* rest) But the second one I can define recursively: prepend_sop z (SOP (S rest)) = let (SOP result) = prepend_sop z (SOP rest) in SOP $ S $ result The definition of `prepend` is the same, albeit with a new type. And, holy shit, it works. If I give Foo and BigFoo additional constructors, data Foo = Foo Int Int | Bar Int Int deriving (Show, GHC.Generic) instance Generic Foo data BigFoo = BigFoo String Int Int | BigBar String Int Int deriving (Show, GHC.Generic) instance Generic BigFoo then the `prepend` function knows which one to choose based on the constructor!
prepend "Hello" (Foo 1 2) :: BigFoo BigFoo "Hello" 1 2
prepend "Hello" (Bar 1 2) :: BigFoo BigBar "Hello" 1 2
Awesome.

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.

On 01/02/2015 01:04 PM, Aleksey Khudyakov wrote:
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
Wow, thanks, this is almost exactly what I've been looking for. My next trick was going to be to combine "convert", "cons", and "tail" operations.
From your example, we can `cons` an "A" to a Foo to get a BigFoo:
H.cons "A" (Foo 1 2) :: BigFoo BigFoo "A" 1 2
And we can `tail` a BigFoo to get a Foo:
H.tail (BigFoo "Hello" 1 2) :: Foo Foo 1 2
But if I combine the two, GHC doesn't know what to do:
H.cons "A" (H.tail (BigFoo "Hello" 1 2)) :: BigFoo
<interactive>:15:1: Couldn't match type ‘H.Elems v0’ with ‘'[Int, Int]’ The type variable ‘v0’ is ambiguous Expected type: [Char] : H.Elems v0 Actual type: H.Elems BigFoo In the expression: H.cons "A" (H.tail (BigFoo "Hello" 1 2)) :: BigFoo In an equation for ‘it’: it = H.cons "A" (H.tail (BigFoo "Hello" 1 2)) :: BigFoo I can make it work in this case by supplying a type signature for the intermediate `tail` expression -- but what if there is no such type? Can I trick it into deducing any old type with the right shape? An intermediate tuple would work, for example. Thanks again.

Wow, thanks, this is almost exactly what I've been looking for. My next trick was going to be to combine "convert", "cons", and "tail" operations.
From your example, we can `cons` an "A" to a Foo to get a BigFoo:
H.cons "A" (Foo 1 2) :: BigFoo BigFoo "A" 1 2
And we can `tail` a BigFoo to get a Foo:
H.tail (BigFoo "Hello" 1 2) :: Foo Foo 1 2
But if I combine the two, GHC doesn't know what to do:
H.cons "A" (H.tail (BigFoo "Hello" 1 2)) :: BigFoo
<interactive>:15:1: Couldn't match type ‘H.Elems v0’ with ‘'[Int, Int]’ The type variable ‘v0’ is ambiguous Expected type: [Char] : H.Elems v0 Actual type: H.Elems BigFoo In the expression: H.cons "A" (H.tail (BigFoo "Hello" 1 2)) :: BigFoo In an equation for ‘it’: it = H.cons "A" (H.tail (BigFoo "Hello" 1 2)) :: BigFoo
I can make it work in this case by supplying a type signature for the intermediate `tail` expression -- but what if there is no such type? Can I trick it into deducing any old type with the right shape? An intermediate tuple would work, for example.
This is problem inherent to very generic code. There could be too many types which could be assigned to intermediate extression. GHC deduce that intermediate type must be isomorphic to (Int,Int) but could not chose such type. We however can always create vector with elements of right type. Library works by converting values to Boehm-Berarducci encoding (ContVec), perform operations on and convert back to concrete representation. So we can fix type of intermediate vector to `ContVec xs` and let GHC to figure out rest. So following will work:
import qualified Data.Vector.HFixed.Cont as H (ContVec) asCont :: H.ContVec a -> H.ContVec a asCont = id
*Main> (H.cons "A" . asCont . H.tail) (BigFoo "Hello" 1 2) :: BigFoo BigFoo "A" 1 2 This function is not in the library but I'm going to add it. It is usefult for combining functions

On 01/02/2015 04:03 PM, Aleksey Khudyakov wrote:
import qualified Data.Vector.HFixed.Cont as H (ContVec) asCont :: H.ContVec a -> H.ContVec a asCont = id
*Main> (H.cons "A" . asCont . H.tail) (BigFoo "Hello" 1 2) :: BigFoo BigFoo "A" 1 2
This function is not in the library but I'm going to add it. It is usefult for combining functions
Ha ha! It works! I have deleted so much code today. I will also be sending you a pull request with millions of tuple instances =)
participants (3)
-
Aleksey Khudyakov
-
Michael Orlitzky
-
Roman Cheplyaka