Records in Haskell

Greg Weber greg at gregweber.info
Thu Feb 23 04:16:54 CET 2012


Thanks to Anthony for his DORF proposal, and spending time to clearly
explain it on the wiki.

I have looked over the main page:
http://hackage.haskell.org/trac/ghc/wiki/Records/DeclaredOverloadedRecordFields

I have a big issue with the approach as presented - it assumes that
record fields with the same name should automatically be shared. As I
have stated before, to avoid circular dependencies, one is forced to
declare types in a single module in Haskell that would ideally be
declared in a multiple modules. Continuing the database example, I
will have multiple tables with a 'name' column, but they do not have
the same meaning.

If I have a function:

  helloName person = "Hello, " ++ person.name

The compiler could infer that I want to say hello to inanimate objects!
Note that I am not completely against abstraction over fields, I just
don't think it is the best default behavior.

And the section "Modules and qualified names for records" shows that
the proposal doesn't fully solve the name-spacing issue.

On Sat, Feb 11, 2012 at 9:43 PM, wren ng thornton <wren at freegeek.org> wrote:
> On 2/11/12 9:47 AM, Greg Weber wrote:
>>
>> What is the use case for changing the type of a record field on update?
>
>
> I use it all the time. One may just as well ask: What is the use case for
> changing the type of a Maybe on update? Or what is the use case for changing
> only one of the types for a tuple update? Records are no different from any
> other polymorphic data type. We don't require special syntax for changing
> Maybe A to Maybe B nor for changing (A,B) to (A,C), so why should we treat
> records any differently?
>
> One particular use case is for records with phantom types. For example, say
> I have a large record which contains both "real" data and also some
> memoization caches for common queries. I don't want to have to recompute the
> caches every time I make a small change to the data, instead I'd like to
> just be able to flip a type-level bit that says "now the caches are dirty".
> This way I can make a bunch of small changes to the main data, and then only
> once that is completed I will recompute the caches (because all the querying
> functions require that the type-level bit says "the caches are
> clean/up-to-date").
>
> There are, of course, non-phantom examples as well. For instance, consider a
> record type for dealing with both sound and unsound versions of some kind of
> yucky data. For example, dealing with commandline argument handling. For the
> first stage of handling we just want to store the raw Strings (or [String]s,
> Maybe Strings,...); but then we'll want to parse those strings into ADTs and
> also perform some sanity checks to make sure the whole configuration is
> sane. One option of doing this is to have our record parametrized by the
> types of the fields, so we're converting from (Yuck String String ...) into
> (Yuck Bool (Maybe (Int,Float)) ...).
>
> For both of these examples it would be possible to monomorphize things to
> have DataDirty/DataClean or YuckRaw/YuckSane. For the latter example, that's
> probably a better choice; but for the former example it is demonstrably
> inferior. And of course it is easy to construct additional examples where
> monomorphization is not actually feasible.
>
> The reason to do this sort of thing as polymorphic records is so that you
> can simultaneously have some functions which care about the type parameters,
> and other functions which do not. Without type-changing updates the only way
> to achieve this is with some convoluted hack like defining a type class over
> all the monomorphic records (and duplicating all the neigh-identical record
> definitions), or using data families which are non-portable. Neither of
> those hacks says what you mean, and both require much more sophisticated
> type analysis than just using type-changing update for records.
> Type-changing update should not be removed, and rendering it into something
> distinct from type-unchanging record update is only coherent for phantom
> type uses of type changes and so cannot apply to non-phantom uses.
>
> --
> Live well,
> ~wren
>
>
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



More information about the Glasgow-haskell-users mailing list