[Haskell-cafe] Return of the revenge of the revisit of the extensible records, reiterated

Atze van der Ploeg atzeus at gmail.com
Fri Dec 6 10:13:20 UTC 2013


You might also wonder why wonder why I use a Sequence instead of a List,
since we only query the head and prepend. This is implement record merge
(.+) more efficiently since we can then use (><) (O(1)) instead of (++)
(O(n)) as follows:

(.++) :: Rec l -> Rec r -> Rec (l :++ r)
(OR l) .++ (OR r) = OR $ M.unionWith (><) l r



2013/12/6 Atze van der Ploeg <atzeus at gmail.com>

> > Thank you Atze for a well-written description.
>
> Cheers! :)
>
> > I think there might be a couple of typos there?
>
> Sadly, due to the finiteness of life I cannot guarantee perfection in all
> my communication. However, if you see typos, I would greatly appreciate it
> if you fix them (it's a wiki). :)
>
> >     (c, r'') = decomp r x      -- rhs s/b: decomp r' x ??
> > Your "motivation" example is hard to follow without knowing what `decomp`
> > does. (IOW, it is not showing me a motivation ;-)
>
> Woops! Sorry! I messed up the example, i've changed it now to:
>
> g :: Rec r -> Rec ("p" ::= String .| r)
> g r = let r' = f (x := 10 .| r)
>           (c,r'') = (r'.!x, r' .- x)
>           v = if c then "Yes" else "Nope"
>       in p := v .| r''
>
>
> > I'm puzzled by this in the implementation notes 4.2 Records:
>
> > "Here we see that a record is actually just a map from string to the
> > sequence of values. Notice that it is a sequence of values and not a
> > single value, because the record may contain duplicate labels."
>
> > It sounds like there's an overhead in being able to support duplicate
> > labels (even if I don't want duplicates in my records)?
> > Is there a performance penalty at run-time with extending/prepending and
> > restricting/pretruncating, to keep the invariant re the i-th value?
>
> Well, supposing you have no duplicate labels, then all sequences are of
> length 1.
> Hence the overhead is that we have a sequence of length 1 instead of just
> a value (i.e. one extra reference to follow).
> This is a very small overhead, and in my opinion is justified by the
> advantages of allowing duplicate labels.
> Notice also that (.!) always accesses the head of the sequence, since only
> the leftmost label is accessible (to access shadowed labels, restrict the
> record with that label).
>
>
> > Leijen allowed duplicate labels to make a virtue of necessity IMO. There
> > has not been an extensible records proposal before or since for duplicate
> > labels. (TRex certainly didn't do it.) His 'necessity' was ease of
> > implementation.
> > This sequence of values stuff seems to make a more difficult
> > implementation for the sake of providing a 'feature' that nobody's asked
> > for(?)
>
> Well, I think Leijen makes two points:
> * Duplicate labels are nice and allow shadowing in records, which is good.
> * Duplicate labels allow us to construct a type system lacking a "lacks"
> predicate, which makes it simpler.
>
> I am mainly interested in the first point, see my example. As I said,
> whether you want duplicate labels depends on the situation.
>
> As another use case for duplicate labels: consider implementing an
> interpreter for some embedded DSL, and you want to carry the
> state of the variables in the an extensible record. Declaring a new
> variable in the embedded language then
> causes us to extend the record. Since the embedded language allows
> shadowing (as most languages do), we can simply
> extend the record, we do not have to jump through hoops to make sure there
> are no duplicate labels. Once the variable
> goes out of scope, we remove the label again to bring the old "variable"
> into scope.
>
> > Actually, I think there's more wrong with that line than a typo:
> >
>
> >     extendUnique :: (..., l :\r ) => ...
> >                   -- s/b: r :\ l  ??
> >
> > (It's supposed to do renaming with non-duplicate labels?)
>
> Sorry! Another mistake, I've fixed it. It is now as follows:
>
> renameUnique :: (KnownSymbol l, KnownSymbol l', r :\ l') => Label l ->
> Label l' -> Rec r -> Rec (Rename l l' r)
>
>
> > Talking of renaming, how does it go with duplicate labels?
> > The comment on `rename` says it can be expressed using the "above
> > operations" (presumably restrict followed by extend with the new label,
> as
> > per Gastar&Jones and Leijen).
>
> > If that's genuinely equivalent, then rename will 'unhide' any duplicate
> > label. So presumably the implementation must split the HashMap into two
> > keys, rather than changing the label on the existing Seq(?)
>
> Yes, exactly. Renaming is implemented as follows, which is equivalent to
> what you said:
>
> rename :: (KnownSymbol l, KnownSymbol l') => Label l -> Label l' -> Rec r -> Rec (Rename l l' r)
> rename l l' r = extend l' (r .! l) (r .- l)
> renameUnique :: (KnownSymbol l, KnownSymbol l', r :\ l') => Label l -> Label l' -> Rec r -> Rec (Rename l l' r)
> renameUnique = rename
>
>
>
>
> 2013/12/6 AntC <anthony_clayden at clear.net.nz>
>
>> > Atze van der Ploeg <atzeus <at> gmail.com> writes:
>> >
>> > (see
>> http://www.haskell.org/haskellwiki/CTRex#Duplicate_labels.2C_and_lacks).
>> > I think duplicate labels are nice in some situations and bad in other
>> situations.
>> >
>>
>> Thank you Atze for a well-written description.
>>
>> I think there might be a couple of typos there?
>>
>>     (c, r'') = decomp r x      -- rhs s/b: decomp r' x ??
>>
>>     extendUnique :: (..., l :\r ) => ...
>>                   -- s/b: r :\ l  ??
>>
>> Your "motivation" example is hard to follow without knowing what `decomp`
>> does. (IOW, it is not showing me a motivation ;-)
>>
>> I'm puzzled by this in the implementation notes 4.2 Records:
>> "Here we see that a record is actually just a map from string to the
>> sequence of values. Notice that it is a sequence of values and not a
>> single value, because the record may contain duplicate labels."
>>
>> It sounds like there's an overhead in being able to support duplicate
>> labels (even if I don't want duplicates in my records)?
>> Is there a performance penalty at run-time with extending/prepending and
>> restricting/pretruncating, to keep the invariant re the i-th value?
>>
>> Leijen allowed duplicate labels to make a virtue of necessity IMO. There
>> has not been an extensible records proposal before or since for duplicate
>> labels. (TRex certainly didn't do it.) His 'necessity' was ease of
>> implementation.
>> This sequence of values stuff seems to make a more difficult
>> implementation for the sake of providing a 'feature' that nobody's asked
>> for(?)
>>
>>
>> There's one 'advanced feature' of extensible records that I'd be
>> interested in: merging records by label, as is done for 'Natural Join'.
>>
>>     a row with labels {x, y, z} merge labels {y, z, w}
>>     returns a Maybe row with {x, y, z, w}
>>     providing the types paired with y and z are the same
>>     and the values are the same
>>     (otherwise return Nothing)
>>
>> It's absolutely essential _not_ to duplicate labels in this case.
>>
>> AntC
>>
>>
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20131206/44b4c671/attachment.html>


More information about the Haskell-Cafe mailing list