<div dir="ltr"><div dir="ltr">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.</div><div dir="ltr"><br></div><div>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.</div><div>runMatrix requires the resulting record to be a Monoid, but it can trivially be provided by changing the wrapper type from Identity to First.<br></div><div><br></div><div>```</div><div> {-# LANGUAGE TypeOperators, PolyKinds, FlexibleContexts, DataKinds #-}<br> <br> import Data.Extensible<br> import Data.Monoid<br> <br> newtype Row g h xs c = Row { unRow :: Comp ((->) (g c)) h :* xs }<br> <br> runMatrix :: Monoid (h :* ys) => Row g h ys :* xs -> g :* xs -> h :* ys<br> runMatrix mat r = hfoldMap getConst<br>   $ hzipWith (\x (Row y) -> Const $ hmap (\(Comp f) -> f x) y) r mat</div><div><br></div><div>isEven :: First :* '[Int] -> First :* '[Bool]<br>isEven = runMatrix<br>   $ Row (Comp (fmap (==0)) <: nil)<br>   <: nil</div><div>```<br></div><br><div class="gmail_quote"><div dir="ltr" class="gmail_attr">2021年10月4日(月) 22:54 Ruben Astudillo <<a href="mailto:ruben.astud@gmail.com" target="_blank">ruben.astud@gmail.com</a>>:<br></div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left:1px solid rgb(204,204,204);padding-left:1ex">Hello cafe<br>
<br>
I have been enjoying the `extensible` package [1] for extensible records and<br>
variants, kudos to the author. I have had a problem of not understanding how<br>
to "massage" data from one representation to another. To exemplify, suppose<br>
I have the following two extensible records<br>
<br>
    {-# language OverloadedLabels #-}<br>
<br>
    import Data.Extensible<br>
    import Control.Lens<br>
<br>
    type Ext1 = Record '[ "field1" >: String, "field2" >: Integer ]<br>
    type Ext2 = Record '[ "field1" >: Text, "field2" >: Double ]<br>
<br>
and I want to map some piece of data between these two types. Currently I am<br>
projecting each field individually like this<br>
<br>
    ex1 :: Ext1<br>
    ex1 = #field1 @= "hello" <: #field2 @= 2.71 <: nil<br>
<br>
    currentMap :: Ext1 -> Ext2<br>
    currentMap s =<br>
      #field1 @= T.pack (view #field1 s)<br>
        <: #field2 @= fromInteger (view #field2 s)<br>
        <: nil<br>
<br>
For data types with few fields it is not so bad. But I have to do this<br>
transformation of data types generated from TH, I am dealing with a few<br>
dozens. The transformations are always from `String -> Text` and `Integer -><br>
Double`. I would like to write a high lever combinator that grabs an<br>
extensible record, transforms each `String` field on a `Text` one and does<br>
the same with `Integer -> Double`.<br>
<br>
Most of the combinators for transforming the data deal with natural<br>
transformations, such as hmap, hsequence and the like. The closest one to<br>
what I want is `hfoldMapFor` where I have to define a class with instances<br>
for all the types the extensible record has, but it doesn't let me change<br>
the type of the result. Does anyone have an idea on how to solve this?<br>
<br>
Thanks for your time.<br>
<br>
[1]: <a href="https://hackage.haskell.org/package/extensible" rel="noreferrer" target="_blank">https://hackage.haskell.org/package/extensible</a><br>
<br>
-- <br>
Rubén. (pgp: 4EE9 28F7 932E F4AD)<br>
_______________________________________________<br>
Haskell-Cafe mailing list<br>
To (un)subscribe, modify options or view archives go to:<br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe</a><br>
Only members subscribed via the mailman list are allowed to post.</blockquote></div></div>