By design, extensible does not provide combinators that change the set of field names (aside from cons and append). Such combinators can easily be abused and make the code difficult to reason about.
Matrix multiplication is one reasonable way to define a dimension-changing transformation. This example demonstrates a function that changes the field from Int to Bool.
runMatrix requires the resulting record to be a Monoid, but it can trivially be provided by changing the wrapper type from Identity to First.
```
{-# LANGUAGE TypeOperators, PolyKinds, FlexibleContexts, DataKinds #-}
import Data.Extensible
import Data.Monoid
newtype Row g h xs c = Row { unRow :: Comp ((->) (g c)) h :* xs }
runMatrix :: Monoid (h :* ys) => Row g h ys :* xs -> g :* xs -> h :* ys
runMatrix mat r = hfoldMap getConst
$ hzipWith (\x (Row y) -> Const $ hmap (\(Comp f) -> f x) y) r mat
isEven :: First :* '[Int] -> First :* '[Bool]
isEven = runMatrix
$ Row (Comp (fmap (==0)) <: nil)
<: nil
```
Hello cafe
I have been enjoying the `extensible` package [1] for extensible records and
variants, kudos to the author. I have had a problem of not understanding how
to "massage" data from one representation to another. To exemplify, suppose
I have the following two extensible records
{-# language OverloadedLabels #-}
import Data.Extensible
import Control.Lens
type Ext1 = Record '[ "field1" >: String, "field2" >: Integer ]
type Ext2 = Record '[ "field1" >: Text, "field2" >: Double ]
and I want to map some piece of data between these two types. Currently I am
projecting each field individually like this
ex1 :: Ext1
ex1 = #field1 @= "hello" <: #field2 @= 2.71 <: nil
currentMap :: Ext1 -> Ext2
currentMap s =
#field1 @= T.pack (view #field1 s)
<: #field2 @= fromInteger (view #field2 s)
<: nil
For data types with few fields it is not so bad. But I have to do this
transformation of data types generated from TH, I am dealing with a few
dozens. The transformations are always from `String -> Text` and `Integer ->
Double`. I would like to write a high lever combinator that grabs an
extensible record, transforms each `String` field on a `Text` one and does
the same with `Integer -> Double`.
Most of the combinators for transforming the data deal with natural
transformations, such as hmap, hsequence and the like. The closest one to
what I want is `hfoldMapFor` where I have to define a class with instances
for all the types the extensible record has, but it doesn't let me change
the type of the result. Does anyone have an idea on how to solve this?
Thanks for your time.
[1]: https://hackage.haskell.org/package/extensible
--
Rubén. (pgp: 4EE9 28F7 932E F4AD)
_______________________________________________
Haskell-Cafe mailing list
To (un)subscribe, modify options or view archives go to:
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
Only members subscribed via the mailman list are allowed to post.