[Haskell-cafe] How to implement this? A case for scoped record labels?

Iavor Diatchki iavor.diatchki at gmail.com
Sun May 31 21:20:23 EDT 2009


Hi,
Using a type class in the way Wren suggests seems to be the right way
to do this in Haskell, as it is at the moment.  I don't think that
this an inappropriate use of type classes at all---in fact, it is
exactly what type classes were designed to do (i.e., allow you to
reuse the same name at different types).  Note that you can combine
type classes and records to cut down on the typing:

data Request = Request { request_channel :: Channel, ... }
data Response = Response { response_channel :: Channel, ... }

class HasChannel t where
  get_channel :: t -> Channel
  set_channel :: Channel -> t -> t

instance HasChannel Request where
  get_channel = request_channel
  set_channel x t = t { response_channel = x }

and so on.  It is a bit verbose, but you only have to do it once for
your protocol, and then you get the nice overloaded interface.
Actually, having the non-overloaded names might also be useful in some
contexts (e.g., to resolve ambiguities).

-Iavor






On Mon, May 25, 2009 at 7:32 PM, wren ng thornton <wren at freegeek.org> wrote:
> ntupel at googlemail.com wrote:
>>
>> This however does not work because record selectors have module scope,
>> so the compiler will complain that channel et. al. are defined
>> multiple times. As a workaround I could put each type into its own
>> module, but at least GHC requires a file per module (which is *very*
>> inconvenient IMO). If we would have scoped labels (e.g. like proposed
>> here: http://legacy.cs.uu.nl/daan/pubs.html#scopedlabels) it seems
>> like it would have been straightforward.
>>
>> So certainly I am missing something and there is a better way to
>> design this. Hence this e-mail. I welcome any advice how this would
>> best be done in Haskell with GHC.
>
> One alternative is to use Haskell's support for ad-hoc overloading. Define a
> typeclass for each selector (or group of selectors that must always occur
> together) which is polymorphic in the record type. Combine this with the
> separate constructor types to get something like:
>
>    data HandshakeRequest = HandshakeRequest String ...
>    data HandshakeResponse = HandshakeResponse String Bool ...
>    ...
>    data BayeuxMessage
>        = HSReq HandshakeRequest
>        | HSRes HandshakeResponse
>        ...
>
>    class BayeuxChannel r where
>        channel :: r -> String
>    instance BayeuxChannel HandshakeRequest where
>        channel (HandshakeRequest ch ...) = ch
>    instance BayeuxChannel HandshakeResponse where
>        channel (HandshakeResponse ch _ ...) = ch
>    ...
>    class BayeuxSuccessful r where
>        successful :: r -> Bool
>    ...
>
>
> It's not pretty, but it gets the job done. Many people decry this as
> improper use of typeclasses though (and rightly so). A better approach would
> probably be to use GADTs or the new data families which give a sort of dual
> of typeclasses (typeclasses give a small set of functions for a large set of
> types; GADTs give a large set of functions for a small set of types[0]).
> Someone more familiar with those approaches should give those versions.
>
> If you want to be able to set the fields as well as read them then the
> classes should be more like lenses than projectors. For instance, this[1]
> discussion on Reddit. The two obvious options are a pair of setter and
> getter functions: (Whole->Part, Whole->Part->Whole); or a factored version
> of the same: Whole->(Part, Part->Whole).
>
> You should also take a look at the data-accessor packages[2][3] which aim to
> give a general solution to the lens problem. Also take a look at hptotoc[4],
> the Haskell implementation of Google's Protocol Buffers which has many
> similar problems to your Bayeaux protocol. In general, protocols designed
> for OO are difficult to translate into non-OO languages.
>
>
>
> [0] http://blog.codersbase.com/tag/gadt/
> [1]
> http://www.reddit.com/r/haskell/comments/86oc3/yet_another_proposal_for_haskell_the_ever_growing/c08f4bp
> [2] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/data-accessor
> [3]
> http://hackage.haskell.org/cgi-bin/hackage-scripts/package/data-accessor-template
> [4] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/hprotoc
>
> --
> Live well,
> ~wren
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list