aeson and dlist in HP 2013.4.0.0

Sean Leather sean.leather at gmail.com
Mon Nov 18 15:15:10 UTC 2013


Hi Joachim,

I did not want to derail the conversation about the pros and cons of dlist,
so I started a separate thread about it on the haskell-platform list [1],
but perhaps I should have included the libraries list [2]. Since a few
people have mentioned concerns about dlist/list conversion, I will respond
below.

On Mon, Nov 18, 2013 at 11:21 AM, Joachim Breitner wrote:

> Am Montag, den 18.11.2013, 10:04 +0200 schrieb Sean Leather:
> > * Maintenance and development taken over by Sean Leather
> > * Migrate repository from http://code.haskell.org/~dons/code/dlist/ to
> >   https://github.com/spl/dlist
> > * Add `Eq`, `Ord`, `Read`, `Show`, `Alternative`, `Foldable`,
> `Traversable`
> >   instances
>
> Given that the point of dlist is to speed up code where lists are
> insufficient,


To be a bit more precise, it is not that lists are "insufficient," the
problem is the `(++)` operator (a.k.a. append). To be even more precise,
the problem is left-nested appends, e.g. the expression `(x ++ y) ++ z` may
have a worse traversal time than `x ++ (y ++ z)`. Such an arrangement can
(and probably will) result in multiple traversals of the left argument(s).

would it make sense to only provide those instances that
> can be implemented without converting to and from lists?
>

In my opinion, no. It makes sense to have as many reasonable instances as
possible to make the library more attractive and usable. The fact that the
instances convert to and from lists does not detract from their usefulness
because the conversions are not necessarily inefficient (see next response).

If there are instances that cannot be implemented idiomatically with
> dlists, maybe they should be left out, to signal the user that he will
> not get the benefits of DLists for these.
>

I think it is an unproven myth that conversion between lists and dlists is
always inefficient. Consider the conversion functions:

> fromList    :: [a] -> DList a
> fromList    = DL . (++)

> toList      :: DList a -> [a]
> toList      = ($[]) . unDL

Converting from a list is like prepending (++) to a list. This introduces a
linear traversal of the argument (assuming a complete evaluation of the
converted list).

 Converting to a list is like "finishing it off" with an empty list. The
operation itself is trivial, but traversing the result would evaluate all
the `(++)` from the previous `fromList`s. Fortunately, all of the
`fromList`ed lists are left-arguments to `(++)`, so each will only be
traversed once (which is the primary reason of dlists).

Looking at the instances in the master branch, most of them use `toList`,
which we have established is trivial. The only instances to use `fromList`
are `Read` and `Traversable`. Each of these reuses the list instance and
involves at least one list traversal, so the extra traversal implied by
`fromList` means a constant factor increase in time.

In particular, it seems that the Show instance could be improved.
> Currently it says
>           showsPrec p dl = showParen (p > 10) $
>             showString "fromList " . shows (toList dl)
> i.e. goes via a list. But this is constructing a ShowS (which is String
> -> String) value, i.e. another difference list. Shouldn’t it be possible
> to stay in the world of difference lists when implementing this?
>

Perhaps you might expect this:

> showsPrec' :: Int -> DList Char -> ShowS
> showsPrec' p dl = showParen (p > 10) $
>   showString "fromList " . unDL dl

But that won't work, because we have a `Show a => DList a`, not a `DList
Char`. The `Show` instance for lists is for `Show a => [a]`, not `[Char]`.
See Bas' dstring library for `DList Char`.

The underlying representation of dlists is `[a] -> [a]`, so what we might
want is a function with the type `Show a => ([a] -> [a]) -> ShowS`. But we
don't need or want to map `String` to `Show a => [a]` as one might think
the higher-order function requires. What we do is finish off the function
with `[]` (which is appended to the end of the resulting list). Then, we're
left with something of type `Show a => [a]`, to which we can apply
`showList`. Looking back at the instance, `toList` finishes the function
and `shows` for `[a]` is equivalent to `showList` for `a`.

(Or maybe I’m overly worried, and I admit that I did not run benchmarks
> so far.)
>

I definitely think benchmarks [3] would help resolve these questions. And
there might be cases where rewrite rules and fusion play a role. But until
then, I remain unconvinced that the added instances are anything but
helpful.

Regards,
Sean

[1]
http://projects.haskell.org/pipermail/haskell-platform/2013-November/002750.html

[2] I assumed the discussion for a library being added (or not) to the
Platform should happen on haskell-platform and not libraries. But perhaps
libraries has more eyes and interest. The fact that many of these emails
are being sent to both lists adds to my confusion about where discussion
should take place.

[3] https://github.com/spl/dlist/issues/3
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/libraries/attachments/20131118/91756dc2/attachment.html>


More information about the Libraries mailing list